heist-1.0.1.0: An Haskell template system supporting both HTML5 and XML.

Safe HaskellNone
LanguageHaskell98

Heist.Internal.Types

Description

Internal types and accessors. There are no guarantees that heist will preserve backwards compatibility for symbols in this module. If you use them, no complaining when your code breaks.

Synopsis

Documentation

type Splices s = MapSyntax Text s Source #

Convenient type alies for splices.

type Template = [Node] Source #

A Template is a forest of XML nodes. Here we deviate from the "single root node" constraint of well-formed XML because we want to allow templates to contain document fragments that may not have a single root.

type MIMEType = ByteString Source #

MIME Type. The type alias is here to make the API clearer.

type TPath = [ByteString] Source #

Reversed list of directories. This holds the path to the template currently being processed.

data DocumentFile Source #

Holds data about templates read from disk.

Constructors

DocumentFile 

data Markup Source #

Designates whether a document should be treated as XML or HTML.

Constructors

Xml 
Html 

newtype RuntimeSplice m a Source #

Monad used for runtime splice execution.

Constructors

RuntimeSplice 

Fields

Instances

data Chunk m Source #

Opaque type representing pieces of output from compiled splices.

Constructors

Pure !ByteString

output known at load time

RuntimeHtml !(RuntimeSplice m Builder)

output computed at run time

RuntimeAction !(RuntimeSplice m ())

runtime action used only for its side-effect

Instances

Show (Chunk m) Source # 

Methods

showsPrec :: Int -> Chunk m -> ShowS #

show :: Chunk m -> String #

showList :: [Chunk m] -> ShowS #

type AttrSplice m = Text -> RuntimeSplice m [(Text, Text)] Source #

Type alias for attribute splices. The function parameter is the value of the bound attribute splice. The return value is a list of attribute key/value pairs that get substituted in the place of the bound attribute.

spliceErrorText :: SpliceError -> Text Source #

Transform a SpliceError record to a Text message.

data CompileException Source #

Exception type for splice compile errors. Wraps the original exception and provides context. data (Exception e) => CompileException e = CompileException

data HeistState m Source #

Holds all the state information needed for template processing. You will build a HeistState using initHeist and any of Heist's HeistState -> HeistState "filter" functions. Then you use the resulting HeistState in calls to renderTemplate.

m is the runtime monad

Constructors

HeistState 

Fields

newtype HeistT n m a Source #

HeistT is the monad transformer used for splice processing. HeistT intentionally does not expose any of its functionality via MonadState or MonadReader functions. We define passthrough instances for the most common types of monads. These instances allow the user to use HeistT in a monad stack without needing calls to lift.

n is the runtime monad (the parameter to HeistState).

m is the monad being run now. In this case, "now" is a variable concept. The type HeistT n n means that "now" is runtime. The type HeistT n IO means that "now" is IO, and more importantly it is NOT runtime. In Heist, the rule of thumb is that IO means load time and n means runtime.

Constructors

HeistT 

Fields

Instances

MonadBase b m => MonadBase b (HeistT n m) Source # 

Methods

liftBase :: b α -> HeistT n m α #

MonadBaseControl b m => MonadBaseControl b (HeistT n m) Source # 

Associated Types

type StM (HeistT n m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (HeistT n m) b -> b a) -> HeistT n m a #

restoreM :: StM (HeistT n m) a -> HeistT n m a #

MonadError e m => MonadError e (HeistT n m) Source #

MonadError passthrough instance

Methods

throwError :: e -> HeistT n m a #

catchError :: HeistT n m a -> (e -> HeistT n m a) -> HeistT n m a #

MonadReader r m => MonadReader r (HeistT n m) Source #

MonadReader passthrough instance

Methods

ask :: HeistT n m r #

local :: (r -> r) -> HeistT n m a -> HeistT n m a #

reader :: (r -> a) -> HeistT n m a #

MonadState s m => MonadState s (HeistT n m) Source #

MonadState passthrough instance

Methods

get :: HeistT n m s #

put :: s -> HeistT n m () #

state :: (s -> (a, s)) -> HeistT n m a #

MonadTrans (HeistT n) Source #

MonadTrans instance

Methods

lift :: Monad m => m a -> HeistT n m a #

MonadTransControl (HeistT n) Source # 

Associated Types

type StT (HeistT n :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (HeistT n) -> m a) -> HeistT n m a #

restoreT :: Monad m => m (StT (HeistT n) a) -> HeistT n m a #

Monad m => Monad (HeistT n m) Source #

Monad instance

Methods

(>>=) :: HeistT n m a -> (a -> HeistT n m b) -> HeistT n m b #

(>>) :: HeistT n m a -> HeistT n m b -> HeistT n m b #

return :: a -> HeistT n m a #

fail :: String -> HeistT n m a #

Functor m => Functor (HeistT n m) Source #

Functor instance

Methods

fmap :: (a -> b) -> HeistT n m a -> HeistT n m b #

(<$) :: a -> HeistT n m b -> HeistT n m a #

MonadFix m => MonadFix (HeistT n m) Source #

MonadFix passthrough instance

Methods

mfix :: (a -> HeistT n m a) -> HeistT n m a #

(Monad m, Functor m) => Applicative (HeistT n m) Source #

Applicative instance

Methods

pure :: a -> HeistT n m a #

(<*>) :: HeistT n m (a -> b) -> HeistT n m a -> HeistT n m b #

(*>) :: HeistT n m a -> HeistT n m b -> HeistT n m b #

(<*) :: HeistT n m a -> HeistT n m b -> HeistT n m a #

(Functor m, MonadPlus m) => Alternative (HeistT n m) Source #

Alternative passthrough instance

Methods

empty :: HeistT n m a #

(<|>) :: HeistT n m a -> HeistT n m a -> HeistT n m a #

some :: HeistT n m a -> HeistT n m [a] #

many :: HeistT n m a -> HeistT n m [a] #

MonadPlus m => MonadPlus (HeistT n m) Source #

MonadPlus passthrough instance

Methods

mzero :: HeistT n m a #

mplus :: HeistT n m a -> HeistT n m a -> HeistT n m a #

MonadIO m => MonadIO (HeistT n m) Source #

MonadIO instance

Methods

liftIO :: IO a -> HeistT n m a #

MonadCont m => MonadCont (HeistT n m) Source #

MonadCont passthrough instance

Methods

callCC :: ((a -> HeistT n m b) -> HeistT n m a) -> HeistT n m a #

type StT (HeistT n) a Source # 
type StT (HeistT n) a = (a, HeistState n)
type StM (HeistT n m) a Source # 
type StM (HeistT n m) a = ComposeSt (HeistT n) m a

templateNames :: HeistState m -> [TPath] Source #

Gets the names of all the templates defined in a HeistState.

compiledTemplateNames :: HeistState m -> [TPath] Source #

Gets the names of all the templates defined in a HeistState.

spliceNames :: HeistState m -> [Text] Source #

Gets the names of all the interpreted splices defined in a HeistState.

compiledSpliceNames :: HeistState m -> [Text] Source #

Gets the names of all the compiled splices defined in a HeistState.

evalHeistT :: Monad m => HeistT n m a -> Node -> HeistState n -> m a Source #

Evaluates a template monad as a computation in the underlying monad.

_liftCatch :: (m (a, HeistState n) -> (e -> m (a, HeistState n)) -> m (a, HeistState n)) -> HeistT n m a -> (e -> HeistT n m a) -> HeistT n m a Source #

Helper for MonadError instance.

_liftCallCC :: ((((a, HeistState n) -> m (b, HeistState n)) -> m (a, HeistState n)) -> m (a, HeistState n)) -> ((a -> HeistT n m b) -> HeistT n m a) -> HeistT n m a Source #

Helper for MonadCont instance.

getParamNode :: Monad m => HeistT n m Node Source #

Gets the node currently being processed.

<speech author="Shakespeare">
  To sleep, perchance to dream.
</speech>

When you call getParamNode inside the code for the speech splice, it returns the Node for the speech tag and its children. getParamNode >>= childNodes returns a list containing one TextNode containing part of Hamlet's speech. liftM (getAttribute "author") getParamNode would return Just "Shakespeare".

localParamNode :: Monad m => (Node -> Node) -> HeistT n m a -> HeistT n m a Source #

HeistT's local.

getsHS :: Monad m => (HeistState n -> r) -> HeistT n m r Source #

HeistT's gets.

getHS :: Monad m => HeistT n m (HeistState n) Source #

HeistT's get.

putHS :: Monad m => HeistState n -> HeistT n m () Source #

HeistT's put.

modifyHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m () Source #

HeistT's modify.

restoreHS :: Monad m => HeistState n -> HeistT n m () Source #

Restores the HeistState. This function is almost like putHS except it preserves the current doctypes and splice errors. You should use this function instead of putHS to restore an old state. This was needed because doctypes needs to be in a "global scope" as opposed to the template call "local scope" of state items such as recursionDepth, curContext, and spliceMap.

localHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m a -> HeistT n m a Source #

Abstracts the common pattern of running a HeistT computation with a modified heist state.

modRecursionDepth :: Monad m => (Int -> Int) -> HeistT n m () Source #

Modifies the recursion depth.

incNamespacedTags :: Monad m => HeistT n m () Source #

Increments the namespaced tag count

data AttAST Source #

AST to hold attribute parsing structure. This is necessary because attoparsec doesn't support parsers running in another monad.

Constructors

Literal Text 
Ident Text 

Instances

type TemplateLocation = IO (Either [String] TemplateRepo) Source #

An IO action for getting a template repo from this location. By not just using a directory path here, we support templates loaded from a database, retrieved from the network, or anything else you can think of.

lens :: Functor f => (t1 -> t) -> (t1 -> a -> b) -> (t -> f a) -> t1 -> f b Source #

My lens creation function to avoid a dependency on lens.

data SpliceConfig m Source #

The splices and templates Heist will use. To bind a splice simply include it in the appropriate place here.

Constructors

SpliceConfig 

Fields

  • _scInterpretedSplices :: Splices (Splice m)

    Interpreted splices are the splices that Heist has always had. They return a list of nodes and are processed at runtime.

  • _scLoadTimeSplices :: Splices (Splice IO)

    Load time splices are like interpreted splices because they return a list of nodes. But they are like compiled splices because they are processed once at load time. All of Heist's built-in splices should be used as load time splices.

  • _scCompiledSplices :: Splices (Splice m)

    Compiled splices return a DList of Chunks and are processed at load time to generate a runtime monad action that will be used to render the template.

  • _scAttributeSplices :: Splices (AttrSplice m)

    Attribute splices are bound to attribute names and return a list of attributes.

  • _scTemplateLocations :: [TemplateLocation]

    A list of all the locations that Heist should get its templates from.

  • _scCompiledTemplateFilter :: TPath -> Bool

    Predicate function to control which templates to compile. Using templates filtered out with this is still possible via callTemplate.

scInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #

Lens for interpreted splices :: Simple Lens (SpliceConfig m) (Splices (I.Splice m))

scLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> SpliceConfig m -> f (SpliceConfig m) Source #

Lens for load time splices :: Simple Lens (SpliceConfig m) (Splices (I.Splice IO))

scCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #

Lens for complied splices :: Simple Lens (SpliceConfig m) (Splices (C.Splice m))

scAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #

Lens for attribute splices :: Simple Lens (SpliceConfig m) (Splices (AttrSplice m))

scTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> SpliceConfig m -> f (SpliceConfig m) Source #

Lens for template locations :: Simple Lens (SpliceConfig m) [TemplateLocation]

scCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> SpliceConfig m -> f (SpliceConfig m) Source #

Lens for compiled template filter :: Simple Lens (SpliceConfig m) (TBool -> Bool)

data HeistConfig m Source #

Constructors

HeistConfig 

Fields

  • _hcSpliceConfig :: SpliceConfig m

    Splices and templates

  • _hcNamespace :: Text

    A namespace to use for all tags that are bound to splices. Use empty string for no namespace.

  • _hcErrorNotBound :: Bool

    Whether to throw an error when a tag wih the heist namespace does not correspond to a bound splice. When not using a namespace, this flag is ignored.

hcSpliceConfig :: Functor f => (SpliceConfig m -> f (SpliceConfig m)) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for the SpliceConfig :: Simple Lens (HeistConfig m) (SpliceConfig m)

hcNamespace :: Functor f => (Text -> f Text) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for the namespace :: Simple Lens (HeistConfig m) Text

hcErrorNotBound :: Functor f => (Bool -> f Bool) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for the namespace error flag :: Simple Lens (HeistConfig m) Bool

hcInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for interpreted splices :: Simple Lens (HeistConfig m) (Splices (I.Splice m))

hcLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for load time splices :: Simple Lens (HeistConfig m) (Splices (I.Splice IO))

hcCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for compiled splices :: Simple Lens (HeistConfig m) (Splices (C.Splice m))

hcAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for attribute splices :: Simple Lens (HeistConfig m) (Splices (AttrSplice m))

hcTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for template locations :: Simple Lens (HeistConfig m) [TemplateLocation]

hcCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> HeistConfig m -> f (HeistConfig m) Source #

Lens for compiled template filter :: Simple Lens (SpliceConfig m) (TBool -> Bool)