Skip to content

Commit

Permalink
improve haddocks
Browse files Browse the repository at this point in the history
  • Loading branch information
soficshift committed Feb 15, 2024
1 parent 754bcfd commit 50372c0
Show file tree
Hide file tree
Showing 6 changed files with 81 additions and 25 deletions.
37 changes: 19 additions & 18 deletions src/Ondim.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,18 +2,22 @@
(implemented in Ondim.MultiWalk.Core).
-}
module Ondim
(-- * Monad
( -- * Monad
Ondim,
runOndimWith,
evalOndimWith,
evalOndim,

-- * Nodes
children,
attributes,
OndimNode,
identify,
ondimCast,
OndimNode,

-- * Children and attributes
children,
expandChildren,
lookupAttr,
attributes,

-- * Running templates
expandNode,
Expand All @@ -30,9 +34,7 @@ module Ondim
getExpansion,
getTemplate,
getNamespace,
getTemplate',
getText,
getText',
-- Calling
callExpansion,
callTemplate,
Expand All @@ -43,11 +45,6 @@ module Ondim
renderNodeOrError,
renderTemplateOrError,

-- * Structure
getSubstructure,
expandChildren,
lookupAttr,

-- * Auxiliary
Attribute,
)
Expand All @@ -58,12 +55,11 @@ import Ondim.MultiWalk.Basic
import Ondim.MultiWalk.Class
import Ondim.MultiWalk.Core
import Ondim.State
import Ondim.MultiWalk.Substructure
import Prelude hiding (All)

-- | Runs the Ondim action with a given initial state.
evalOndimWith ::
Monad m =>
(Monad m) =>
OndimState m ->
Ondim m a ->
m (Either OndimException a)
Expand All @@ -75,7 +71,7 @@ evalOndimWith s o =

-- | Runs the Ondim action with a given initial state, and also return the final state.
runOndimWith ::
Monad m =>
(Monad m) =>
OndimState m ->
Ondim m a ->
m (Either OndimException (a, OndimState m))
Expand All @@ -86,12 +82,17 @@ runOndimWith s o =
`runStateT` s

-- | Runs the Ondim action with empty initial state.
evalOndim :: Monad m => Ondim m a -> m (Either OndimException a)
evalOndim :: (Monad m) => Ondim m a -> m (Either OndimException a)
evalOndim = evalOndimWith mempty

-- Children

-- | Returns the children of a node after expanding them.
{- | Returns the children of a node after expanding them.
@
'expandChildren' = 'expandNodes' . 'children'
@
-}
expandChildren ::
forall t m.
(OndimNode t, Monad m) =>
Expand All @@ -109,7 +110,7 @@ lookupAttr ::
lookupAttr key = fmap (L.lookup key) . attributes

-- | Render node as bytestring, if possible, or fail.
renderNodeOrError :: (HasCallStack, Monad m) => OndimNode a => a -> Ondim m LByteString
renderNodeOrError :: (HasCallStack, Monad m) => (OndimNode a) => a -> Ondim m LByteString
renderNodeOrError =
case renderNode of
Just render -> return . render
Expand All @@ -133,7 +134,7 @@ callTemplate name = do
either (throwExpFailure @t name) return exps

-- | Either applies text 'name', or throws a failure if it does not exist.
callText :: Monad m => Text -> Ondim m Text
callText :: (Monad m) => Text -> Ondim m Text
callText name = do
exps <- getText name
either (throwExpFailure @Text name) return exps
Expand Down
4 changes: 4 additions & 0 deletions src/Ondim/Advanced.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,11 @@ module Ondim.Advanced

-- * Combinators
module Ondim.MultiWalk.Combinators,

-- * Substructures
module Ondim.MultiWalk.Substructure,
) where

import Ondim.MultiWalk.Class (OndimNode (..))
import Ondim.MultiWalk.Combinators
import Ondim.MultiWalk.Substructure
14 changes: 11 additions & 3 deletions src/Ondim/MultiWalk/Basic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,10 +81,18 @@ type PolyExpansion m = forall a. (OndimNode a, Monad m) => Expansion m a

-- | An opaque datatype that should be regarded as a sum of four possible types:
--
-- 1. Typed expansions, i.e., expansions that apply to a single type (use
-- 'Ondim.State.typedExpansion' to create).
-- 1. Typed expansions, i.e., expansions that apply to a single type (use the
-- 'Ondim.State.typedExpansion' constructor).
--
-- 2. Polymorphic expansions
-- 2. Polymorphic expansions, i.e., expansions that are polymophic over types
-- with 'OndimNode' instances (use the 'Ondim.State.polyExpansion'
-- constructor).
--
-- 3. Templates, i.e., raw node data that represents templates. (use the
-- 'Ondim.State.templateData' constructor).
--
-- 4. Namespaces, i.e., nested namespaces. (use the 'Ondim.State.namespace'
-- constructor).
data NamespaceItem m where
TypedExpansion :: TypeRep a -> DefinitionSite -> Expansion m a -> NamespaceItem m
PolyExpansion :: DefinitionSite -> PolyExpansion m -> NamespaceItem m
Expand Down
10 changes: 10 additions & 0 deletions src/Ondim/MultiWalk/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,16 +51,26 @@ class (OndimNodeC t) => OndimNode t where
type ExpTypes t :: Spec
type NodeListSpec t :: Type
type NodeListSpec t = NLDef t

-- | Returns the name of the node as defined by the 'OndimNode' instance.
identify :: t -> Maybe Text
identify _ = Nothing

-- | Returns a list of attributes of the node as defined by the 'OndimNode' instance.
attributes :: (Monad m) => t -> Ondim m [Attribute]
attributes _ = pure []

-- | Returns the children of the node as defined by the 'OndimNode' instance.
children :: t -> [t]
children _ = []

castFrom :: (Typeable a) => Proxy a -> Maybe (a -> [t])
castFrom _ = Nothing

-- | Converts the node to a 'LByteString' as defined by the 'OndimNode' instance.
renderNode :: Maybe (t -> LByteString)
renderNode = Nothing

nodeAsText :: Maybe (t -> Text)
nodeAsText = Nothing

Expand Down
4 changes: 2 additions & 2 deletions src/Ondim/MultiWalk/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -160,8 +160,8 @@ expCtx name site (Ondim ctx) = do
More precisely, if the node name matches the name of a bound expansion, then
it feeds the node directly into the expansion. Otherwise, it runs
@liftSubstuctures@ on the node, which essentially amounts to running
@liftNode@ on each substructure.
'expandSubstructures' on the node, which essentially amounts to running
'expandNode' on each substructure.
-}
expandNode ::
forall t m.
Expand Down
37 changes: 35 additions & 2 deletions src/Ondim/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@

module Ondim.State
( -- * Namespace maps

NamespaceMap,
binding,
mapToNamespace,
Expand Down Expand Up @@ -113,6 +112,7 @@ infixr 0 #<>
(#<>) :: Text -> Maybe (NamespaceItem m) -> NamespaceMap m
name #<> ex = NamespaceMapM $ modify' ((name, ex) :)

-- | Remove a previously added item from the 'NamespaceMap'.
unbind :: Text -> NamespaceMap m
unbind k = k #<> Nothing

Expand Down Expand Up @@ -140,6 +140,7 @@ type NamespaceMap m = NamespaceMapM m ()

infixr 0 #:

-- | Infix to add a 'NamespaceItem' to a 'NamespaceMap'.
(#:) :: Text -> NamespaceItem m -> NamespaceMap m
name #: ex = name #<> Just ex

Expand All @@ -151,6 +152,12 @@ typedExpansion' = TypedExpansion typeRep

infixr 0 ##

{- | Infix to add an 'Expansion' to a 'NamespaceMap'.
@
name '##' expansion = name '#:' 'typedExpansion' expansion
@
-}
(##) :: (HasCallStack, Typeable t) => Text -> Expansion m t -> NamespaceMap m
name ## ex = name #: typedExpansion ex

Expand All @@ -162,6 +169,13 @@ templateData' = Template typeRep

infixr 0 #%

{- | Infix to add a template (any type with an 'OndimNode' instance) to a
'NamespaceMap'.
@
name '#%' template = name '#:' 'templateData' template
@
-}
(#%) :: (HasCallStack, OndimNode a) => Text -> a -> NamespaceMap m
name #% ex = name #: templateData ex

Expand All @@ -173,8 +187,15 @@ textData' = templateData'

infixr 0 #@

{- | Infix to add a textual data to a 'NamespaceMap'. Just a specialized version
of '#%'.
@
name '#@' text = name '#:' 'textData' text
@
-}
(#@) :: (HasCallStack) => Text -> Text -> NamespaceMap m
name #@ ex = name #% ex
(#@) = (#%)

polyExpansion :: (HasCallStack) => PolyExpansion m -> NamespaceItem m
polyExpansion = PolyExpansion callStackSite
Expand All @@ -184,6 +205,12 @@ polyExpansion' = PolyExpansion

infixr 0 #*

{- | Infix to add a t'PolyExpansion' to a 'NamespaceMap'.
@
name '#*' expansion = name '#:' 'polyExpansion' expansion
@
-}
(#*) :: (HasCallStack) => Text -> PolyExpansion m -> NamespaceMap m
name #* ex = name #: polyExpansion ex

Expand All @@ -202,6 +229,12 @@ namespace' = NamespaceData

infixr 0 #.

{- | Infix to nest a 'NamespaceMap' inside a 'NamespaceMap'.
@
name '#.' nsMap = name '#:' 'namespace' nsMap
@
-}
(#.) :: Text -> NamespaceMap m -> NamespaceMap m
name #. ex = name #: namespace ex

Expand Down

0 comments on commit 50372c0

Please sign in to comment.