doctemplates-0.4: Pandoc-style document templates

CopyrightCopyright (C) 2009-2019 John MacFarlane
LicenseBSD3
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.DocTemplates

Description

The text templating system used by pandoc.

Example of use

import Data.Text (Text)
import qualified Data.Text.IO as T
import Data.Aeson
import Text.DocTemplates

data Employee = Employee { firstName :: String
                         , lastName  :: String
                         , salary    :: Maybe Int }
instance ToJSON Employee where
  toJSON e = object [ "name" .= object [ "first" .= firstName e
                                       , "last"  .= lastName e ]
                    , "salary" .= salary e ]

template :: Text
template = "$for(employee)$Hi, $employee.name.first$. $if(employee.salary)$You make $employee.salary$.$else$No salary data.$endif$$sep$\n$endfor$"

main :: IO ()
main = do
  res <- compileTemplate "mytemplate.txt" template
  case res of
         Left e    -> error e
         Right t   -> T.putStrLn $ renderTemplate t $ object
                        ["employee" .=
                          [ Employee "John" "Doe" Nothing
                          , Employee "Omar" "Smith" (Just 30000)
                          , Employee "Sara" "Chen" (Just 60000) ]
                        ]

Delimiters

To mark variables and control structures in the template, either $$ or ${} may be used as delimiters. The styles may also be mixed in the same template, but the opening and closing delimiter must match in each case. The opening delimiter may be followed by one or more spaces or tabs, which will be ignored. The closing delimiter may be followed by one or more spaces or tabs, which will be ignored.

To include a literal $ in the document, use $$.

Comments

Anything between the sequence $-- and the end of the line will be treated as a comment and omitted from the output.

Interpolated variables

A slot for an interpolated variable is a variable name surrounded by matched delimiters. Variable names must begin with a letter and can contain letters, numbers, _, -, and .. The keywords it, if, else, endif, for, sep, and endfor may not be used as variable names. Examples:

$foo$
$foo.bar.baz$
$foo_bar.baz-bim$
$ foo $
${foo}
${foo.bar.baz}
${foo_bar.baz-bim}
${ foo }

The values of variables are determined by a JSON object that is passed as a parameter to renderTemplate. So, for example, title will return the value of the title field, and employee.salary will return the value of the salary field of the object that is the value of the employee field.

  • If the value of the variable is a JSON string, the string will be rendered verbatim. (Note that no escaping is done on the string; the assumption is that the calling program will escape the strings appropriately for the output format.)
  • If the value is a JSON array, the values will be concatenated.
  • If the value is a JSON object, the string true will be rendered.
  • If the value is a JSON number, it will be rendered as an integer if possible, otherwise as a floating-point number.
  • If the value is a JSON boolean, it will be rendered as true if true, and as the empty string if false.
  • Every other value will be rendered as the empty string.

The value of a variable that occurs by itself on a line will be indented to the same level as the opening delimiter of the variable.

Conditionals

A conditional begins with if(variable) (enclosed in matched delimiters) and ends with endif (enclosed in matched delimiters). It may optionally contain an else (enclosed in matched delimiters). The if section is used if variable has a non-empty value, otherwise the else section is used (if present). (Note that even the string false counts as a true value.) Examples:

$if(foo)$bar$endif$

$if(foo)$
  $foo$
$endif$

$if(foo)$
part one
$else$
part two
$endif$

${if(foo)}bar${endif}

${if(foo)}
  ${foo}
${endif}

${if(foo)}
${ foo.bar }
${else}
no foo!
${endif}

Conditional keywords should not be indented, or unexpected spacing problems may occur.

For loops

A for loop begins with for(variable) (enclosed in matched delimiters) and ends with endfor (enclosed in matched delimiters. If variable is an array, the material inside the loop will be evaluated repeatedly, with variable being set to each value of the array in turn. If the value of the associated variable is not an array, a single iteration will be performed on its value.

Examples:

$for(foo)$$foo$$sep$, $endfor$

$for(foo)$
  - $foo.last$, $foo.first$
$endfor$

${ for(foo.bar) }
  - ${ foo.bar.last }, ${ foo.bar.first }
${ endfor }

You may optionally specify a separator between consecutive values using sep (enclosed in matched delimiters). The material between sep and the endfor is the separator.

${ for(foo) }${ foo }${ sep }, ${ endfor }

Instead of using variable inside the loop, the special anaphoric keyword it may be used.

${ for(foo.bar) }
  - ${ it.last }, ${ it.first }
${ endfor }

Partials

Partials (subtemplates stored in different files) may be included using the syntax

${ boilerplate() }

The partials are obtained using getPartial from the TemplateMonad class. This may be implemented differently in different monads. The path passed to getPartial is computed on the basis of the original template path (a parameter to compileTemplate) and the partial’s name. The partial’s name is substituted for the base name of the original template path (leaving the original template’s extension), unless the partial has an explicit extension, in which case this is kept. So, with the TemplateMonad instance for IO, partials will be sought in the directory containing the main template, and will be assumed to have the extension of the main template.

Partials may optionally be applied to variables using a colon:

${ date:fancy() }

${ articles:bibentry() }

If articles is an array, this will iterate over its values, applying the partial bibentry() to each one. So the second example above is equivalent to

${ for(articles) }
${ it:bibentry() }
${ endfor }

Note that the anaphoric keyword it must be used when iterating over partials. In the above examples, the bibentry partial should contain it.title (and so on) instead of articles.title.

Final newlines are omitted from included partials.

Partials may include other partials. If you exceed a nesting level of 50, though, in resolving partials, the literal (loop) will be returned, to avoid infinite loops.

A separator between values of an array may be specified in square brackets, immediately after the variable name or partial:

${months[, ]}$

${articles:bibentry()[; ]$

The separator in this case is literal and (unlike with sep in an explicit for loop) cannot contain interpolated variables or other template directives.

Synopsis

Documentation

renderTemplate :: (TemplateTarget a, ToContext b a) => Template -> b -> a Source #

Render a compiled template in a "context" which provides values for the template's variables.

compileTemplate :: TemplateMonad m => FilePath -> Text -> m (Either String Template) Source #

Compile a template. The FilePath parameter is used to determine a default path and extension for partials and may be left empty if partials are not used.

compileTemplateFile :: FilePath -> IO (Either String Template) Source #

Compile a template from a file. IO errors will be raised as exceptions; template parsing errors result in Left return values.

applyTemplate :: (TemplateMonad m, TemplateTarget a, ToContext b a) => FilePath -> Text -> b -> m (Either String a) Source #

Compile a template and apply it to a context. This is just a convenience function composing compileTemplate and renderTemplate. If a template will be rendered more than once in the same process, compile it separately for better performance.

class Monad m => TemplateMonad m where Source #

A TemplateMonad defines a function to retrieve a partial (from the file system, from a database, or using a default value).

class Monoid a => TemplateTarget a where Source #

A type to which templates can be rendered.

Methods

fromText :: Text -> a Source #

removeFinalNewline :: a -> a Source #

isEmpty :: a -> Bool Source #

indent :: Int -> a -> a Source #

newtype Context a Source #

A Context defines values for template's variables.

Constructors

Context 

Fields

Instances
Functor Context Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fmap :: (a -> b) -> Context a -> Context b #

(<$) :: a -> Context b -> Context a #

Foldable Context Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fold :: Monoid m => Context m -> m #

foldMap :: Monoid m => (a -> m) -> Context a -> m #

foldr :: (a -> b -> b) -> b -> Context a -> b #

foldr' :: (a -> b -> b) -> b -> Context a -> b #

foldl :: (b -> a -> b) -> b -> Context a -> b #

foldl' :: (b -> a -> b) -> b -> Context a -> b #

foldr1 :: (a -> a -> a) -> Context a -> a #

foldl1 :: (a -> a -> a) -> Context a -> a #

toList :: Context a -> [a] #

null :: Context a -> Bool #

length :: Context a -> Int #

elem :: Eq a => a -> Context a -> Bool #

maximum :: Ord a => Context a -> a #

minimum :: Ord a => Context a -> a #

sum :: Num a => Context a -> a #

product :: Num a => Context a -> a #

Traversable Context Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Context a -> f (Context b) #

sequenceA :: Applicative f => Context (f a) -> f (Context a) #

mapM :: Monad m => (a -> m b) -> Context a -> m (Context b) #

sequence :: Monad m => Context (m a) -> m (Context a) #

Show a => Show (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

showsPrec :: Int -> Context a -> ShowS #

show :: Context a -> String #

showList :: [Context a] -> ShowS #

Semigroup (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

(<>) :: Context a -> Context a -> Context a #

sconcat :: NonEmpty (Context a) -> Context a #

stimes :: Integral b => b -> Context a -> Context a #

Monoid (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

mempty :: Context a #

mappend :: Context a -> Context a -> Context a #

mconcat :: [Context a] -> Context a #

ToContext (Context a) a Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Context a -> Context a Source #

data Val a Source #

A variable value.

Constructors

SimpleVal a 
ListVal [Val a] 
MapVal (Context a) 
NullVal 
Instances
Functor Val Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fmap :: (a -> b) -> Val a -> Val b #

(<$) :: a -> Val b -> Val a #

Foldable Val Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fold :: Monoid m => Val m -> m #

foldMap :: Monoid m => (a -> m) -> Val a -> m #

foldr :: (a -> b -> b) -> b -> Val a -> b #

foldr' :: (a -> b -> b) -> b -> Val a -> b #

foldl :: (b -> a -> b) -> b -> Val a -> b #

foldl' :: (b -> a -> b) -> b -> Val a -> b #

foldr1 :: (a -> a -> a) -> Val a -> a #

foldl1 :: (a -> a -> a) -> Val a -> a #

toList :: Val a -> [a] #

null :: Val a -> Bool #

length :: Val a -> Int #

elem :: Eq a => a -> Val a -> Bool #

maximum :: Ord a => Val a -> a #

minimum :: Ord a => Val a -> a #

sum :: Num a => Val a -> a #

product :: Num a => Val a -> a #

Traversable Val Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Val a -> f (Val b) #

sequenceA :: Applicative f => Val (f a) -> f (Val a) #

mapM :: Monad m => (a -> m b) -> Val a -> m (Val b) #

sequence :: Monad m => Val (m a) -> m (Val a) #

FromContext a (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fromVal :: Val a -> Maybe (Val a) Source #

lookupContext :: Text -> Context a -> Maybe (Val a) Source #

Show a => Show (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

showsPrec :: Int -> Val a -> ShowS #

show :: Val a -> String #

showList :: [Val a] -> ShowS #

class ToContext b a where Source #

The ToContext class provides automatic conversion to a Context.

Methods

toContext :: b -> Context a Source #

Instances
TemplateTarget a => ToContext Value a Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Value -> Context a Source #

ToContext (Context a) a Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Context a -> Context a Source #

class FromContext a b where Source #

The FromContext class provides functions for extracting values from Val and Context.

Minimal complete definition

fromVal

Methods

fromVal :: Val a -> Maybe b Source #

lookupContext :: Text -> Context a -> Maybe b Source #

Instances
FromContext a a Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fromVal :: Val a -> Maybe a Source #

lookupContext :: Text -> Context a -> Maybe a Source #

FromContext a [a] Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fromVal :: Val a -> Maybe [a] Source #

lookupContext :: Text -> Context a -> Maybe [a] Source #

FromContext a (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

fromVal :: Val a -> Maybe (Val a) Source #

lookupContext :: Text -> Context a -> Maybe (Val a) Source #

data Template Source #

A template.

Instances
Eq Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Data Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Template -> c Template #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Template #

toConstr :: Template -> Constr #

dataTypeOf :: Template -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Template) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Template) #

gmapT :: (forall b. Data b => b -> b) -> Template -> Template #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Template -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Template -> r #

gmapQ :: (forall d. Data d => d -> u) -> Template -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Template -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Template -> m Template #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Template -> m Template #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Template -> m Template #

Ord Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Read Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Show Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Generic Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Associated Types

type Rep Template :: Type -> Type #

Methods

from :: Template -> Rep Template x #

to :: Rep Template x -> Template #

Semigroup Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Monoid Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

type Rep Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

type Rep Template = D1 (MetaData "Template" "Text.DocTemplates.Internal" "doctemplates-0.4-C5An5aDeaka9UlLPqVrzrX" False) ((C1 (MetaCons "Interpolate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Indented) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Variable)) :+: (C1 (MetaCons "Conditional" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Variable) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Template) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Template))) :+: C1 (MetaCons "Iterate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Variable) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Template) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Template))))) :+: ((C1 (MetaCons "Partial" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Template)) :+: C1 (MetaCons "Literal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) :+: (C1 (MetaCons "Concat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Template) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Template)) :+: C1 (MetaCons "Empty" PrefixI False) (U1 :: Type -> Type))))