doctemplates-0.10.0.1: Pandoc-style document templates
CopyrightCopyright (C) 2009-2019 John MacFarlane
LicenseBSD3
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.DocTemplates

Description

This is the text templating system used by pandoc. Its basic function is to fill variables in a template. Variables are provided by a “context.” Any instance of the ToContext typeclass (such as an aeson Value) can serve as the context, or a Context value can be constructed manually.

Control structures are provided to test whether a variable has a non-blank value and to iterate over the items of a list. Partials—that is, subtemplates defined in different files—are supported. Pipes can be used to transform the values of variables or partials. The provided pipes make it possible to do list enumeration and tabular layout in templates.

Templates are rendered to a doclayout Doc (which is polymorphic in the underlying string type). If Doc values are used in the context, rendered documents will be able to wrap flexibly on breaking spaces. This feature makes doctemplates more suitable than other template engines for plain-text formats (like Markdown).

Unlike the various HTML-centered template engines, doctemplates is output-format agnostic, so no automatic escaping is done on interpolated values. Values are assumed to be escaped properly in the Context.

Example of use

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

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 $ render Nothing $ 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 the Context 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 simple value, it will be rendered verbatim. (Note that no escaping is done; the assumption is that the calling program will escape the strings appropriately for the output format.)
  • If the value of the variable is a boolean value, it will be rendered as true if true, or as empty if false.
  • If the value is a list, the values will be concatenated.
  • If the value is a map, the string true will be rendered.
  • Every other value will be rendered as the empty string.

When a Context is derived from an aeson (JSON) Value, the following conversions are done:

  • If the value is a number, it will be rendered as an integer if possible, otherwise as a floating-point number.

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 true value, otherwise the else section is used (if present). The following values count as true:

  • any map
  • any array containing at least one true value
  • any nonempty string (even false)
  • boolean True

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}

The keyword elseif may be used to simplify complex nested conditionals. Thus

$if(foo)$
XXX
$elseif(bar)$
YYY
$else$
ZZZ
$endif$

is equivalent to

$if(foo)$
XXX
$else$
$if(bar)$
YYY
$else$
ZZZ
$endif$
$endif$

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, and concatenated.
  • If variable is a map, the material inside will be set to the map.
  • If the value of the associated variable is not an array or a map, 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 }

$for(mymap)$
$it.name$: $it.office$
$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.

Nesting

To ensure that content is “nested,” that is, subsequent lines indented, use the ^ directive:

$item.number$  $^$$item.description$ ($item.price$)

In this example, if item.description has multiple lines, they will all be indented to line up with the first line:

00123  A fine bottle of 18-year old
       Oban whiskey. ($148)

To nest multiple lines to the same level, align them with the ^ directive in the template. For example:

$item.number$  $^$$item.description$ ($item.price$)
               (Available til $item.sellby$.)

will produce

00123  A fine bottle of 18-year old
       Oban whiskey. ($148)
       (Available til March 30, 2020.)

If a variable occurs by itself on a line, preceded by whitespace and not followed by further text or directives on the same line, and the variable’s value contains multiple lines, it will be nested automatically.

Breakable spaces

When rendering to a Doc, a distinction can be made between breakable and unbreakable spaces. Normally, spaces in the template itself (as opposed to values of the interpolated variables) are not breakable, but they can be made breakable in part of the template by using the ~ keyword (ended with another ~).

$~$This long line may break if the document is rendered
with a short line length.$~$

The ~ keyword has no effect when rendering to Text or String.

Pipes

A pipe transforms the value of a variable or partial. Pipes are specified using a slash (/) between the variable name (or partial) and the pipe name. Example:

$for(name)$
$name/uppercase$
$endfor$

$for(metadata/pairs)$
- $it.key$: $it.value$
$endfor$

$employee:name()/uppercase$

Pipes may be chained:

$for(employees/pairs)$
$it.key/alpha/uppercase$. $it.name$
$endfor$

Some pipes take parameters:

|----------------------|------------|
$for(employee)$
$it.name.first/uppercase/left 20 "| "$$it.name.salary/right 10 " | " " |"$
$endfor$
|----------------------|------------|

Currently the following pipes are predefined:

  • pairs: Converts a map or array to an array of maps, each with key and value fields. If the original value was an array, the key will be the array index, starting with 1.
  • first: Returns the first value of an array, if applied to a non-empty array; otherwise returns the original value.
  • last: Returns the last value of an array, if applied to a non-empty array; otherwise returns the original value.
  • rest: Returns all but the first value of an array, if applied to a non-empty array; otherwise returns the original value.
  • allbutlast: Returns all but the last value of an array, if applied to a non-empty array; otherwise returns the original value.
  • uppercase: Converts text to uppercase.
  • lowercase: Converts text to lowercase.
  • length: Returns the length of the value: number of characters for a textual value, number of elements for a map or array.
  • reverse: Reverses a textual value or array, and has no effect on other values.
  • chomp: Removes trailing newlines (and breakable space).
  • nowrap: Disables line wrapping on breakable spaces.
  • alpha: Converts textual values that can be read as an integer into lowercase alphabetic characters a..z (mod 26). This can be used to get lettered enumeration from array indices. To get uppercase letters, chain with uppercase.
  • roman: Converts textual values that can be read as an integer into lowercase roman numerials. This can be used to get lettered enumeration from array indices. To get uppercase roman, chain with uppercase.
  • left n "leftborder" "rightborder": Renders a textual value in a block of width n, aligned to the left, with an optional left and right border. Has no effect on other values. This can be used to align material in tables. Widths are positive integers indicating the number of characters. Borders are strings inside double quotes; literal " and \ characters must be backslash-escaped.
  • right n "leftborder" "rightborder": Renders a textual value in a block of width n, aligned to the right, and has no effect on other values.
  • center n "leftborder" "rightborder": Renders a textual value in a block of width n, aligned to the center, and has no effect on other values.
Synopsis

Documentation

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

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

compileTemplate :: (TemplateMonad m, TemplateTarget a) => FilePath -> Text -> m (Either String (Template a)) 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 :: TemplateTarget a => FilePath -> IO (Either String (Template a)) 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 a b) => FilePath -> Text -> b -> m (Either String (Doc 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).

Instances

Instances details
TemplateMonad IO Source # 
Instance details

Defined in Text.DocTemplates.Internal

TemplateMonad Identity Source # 
Instance details

Defined in Text.DocTemplates.Internal

newtype Context a Source #

A Context defines values for template's variables.

Constructors

Context 

Fields

Instances

Instances details
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 #

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) #

ToContext a (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Context a -> Context a Source #

toVal :: Context a -> Val a Source #

Data a => Data (Context a) 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) -> Context a -> c (Context a) #

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

toConstr :: Context a -> Constr #

dataTypeOf :: Context a -> DataType #

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

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

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

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

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

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

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

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

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

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Context 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 #

TemplateTarget a => FromYAML (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

parseYAML :: Node Pos -> Parser (Context a) #

TemplateTarget a => ToYAML (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toYAML :: Context a -> Node () #

TemplateTarget a => ToJSON (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

TemplateTarget a => FromJSON (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

data Val a Source #

A variable value.

Constructors

SimpleVal (Doc a) 
ListVal [Val a] 
MapVal (Context a) 
BoolVal Bool 
NullVal 

Instances

Instances details
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 #

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) #

TemplateTarget 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 #

ToContext a (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Val a -> Context a Source #

toVal :: Val a -> Val a Source #

Data a => Data (Val a) 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) -> Val a -> c (Val a) #

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

toConstr :: Val a -> Constr #

dataTypeOf :: Val a -> DataType #

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

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

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

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

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

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

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

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

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

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

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 #

TemplateTarget a => FromYAML (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

parseYAML :: Node Pos -> Parser (Val a) #

TemplateTarget a => ToYAML (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toYAML :: Val a -> Node () #

TemplateTarget a => ToJSON (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toJSON :: Val a -> Value #

toEncoding :: Val a -> Encoding #

toJSONList :: [Val a] -> Value #

toEncodingList :: [Val a] -> Encoding #

TemplateTarget a => FromJSON (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

parseJSON :: Value -> Parser (Val a) #

parseJSONList :: Value -> Parser [Val a] #

class ToContext a b where Source #

The ToContext class provides automatic conversion to a Context or Val.

Minimal complete definition

toVal

Methods

toContext :: b -> Context a Source #

toVal :: b -> Val a Source #

Instances

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

Defined in Text.DocTemplates.Internal

TemplateTarget a => ToContext a Bool Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Bool -> Context a Source #

toVal :: Bool -> Val a Source #

TemplateTarget a => ToContext a a Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: a -> Context a Source #

toVal :: a -> Val a Source #

ToContext a b => ToContext a [b] Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: [b] -> Context a Source #

toVal :: [b] -> Val a Source #

ToContext a a => ToContext a (Doc a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Doc a -> Context a Source #

toVal :: Doc a -> Val a Source #

ToContext a (Val a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Val a -> Context a Source #

toVal :: Val a -> Val a Source #

ToContext a (Context a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Context a -> Context a Source #

toVal :: Context a -> Val a Source #

ToContext a b => ToContext a (Map Text b) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Map Text b -> Context a Source #

toVal :: Map Text b -> Val a Source #

TemplateTarget [a] => ToContext [a] [a] Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: [a] -> Context [a] Source #

toVal :: [a] -> Val [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

Instances details
TemplateTarget a => 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 b => FromContext a [b] Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

TemplateTarget a => FromContext a (Doc a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

TemplateTarget 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 #

TemplateTarget [a] => 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 #

data Template a Source #

A template.

Instances

Instances details
Functor Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

Foldable Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Template a -> m #

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

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

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

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

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

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

toList :: Template a -> [a] #

null :: Template a -> Bool #

length :: Template a -> Int #

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

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

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

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

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

Traversable Template Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

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

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

Eq a => Eq (Template a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

(==) :: Template a -> Template a -> Bool #

(/=) :: Template a -> Template a -> Bool #

Data a => Data (Template a) 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 a -> c (Template a) #

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

toConstr :: Template a -> Constr #

dataTypeOf :: Template a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Template a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

compare :: Template a -> Template a -> Ordering #

(<) :: Template a -> Template a -> Bool #

(<=) :: Template a -> Template a -> Bool #

(>) :: Template a -> Template a -> Bool #

(>=) :: Template a -> Template a -> Bool #

max :: Template a -> Template a -> Template a #

min :: Template a -> Template a -> Template a #

Read a => Read (Template a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

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

Defined in Text.DocTemplates.Internal

Methods

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

show :: Template a -> String #

showList :: [Template a] -> ShowS #

Generic (Template a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Associated Types

type Rep (Template a) :: Type -> Type #

Methods

from :: Template a -> Rep (Template a) x #

to :: Rep (Template a) x -> Template a #

Semigroup a => Semigroup (Template a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

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

Semigroup a => Monoid (Template a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

mempty :: Template a #

mappend :: Template a -> Template a -> Template a #

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

type Rep (Template a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

type Rep (Template a) = D1 ('MetaData "Template" "Text.DocTemplates.Internal" "doctemplates-0.10.0.1-CSajvuX1NaGgqjKak8gA9" 'False) (((C1 ('MetaCons "Interpolate" 'PrefixI 'False) (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 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Template a))))) :+: (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 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Template a)))) :+: C1 ('MetaCons "Nested" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Template a))))) :+: ((C1 ('MetaCons "Partial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pipe]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Template a))) :+: C1 ('MetaCons "Literal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)))) :+: (C1 ('MetaCons "Concat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Template a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Template a))) :+: C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type))))

data Doc a #

Document, including structure relevant for layout.

Constructors

Text Int a

Text with specified width.

Block Int [a]

A block with a width and lines.

VFill Int a

A vertically expandable block; when concatenated with a block, expands to height of block, with each line containing the specified text.

Prefixed Text (Doc a)

Doc with each line prefixed with text. Note that trailing blanks are omitted from the prefix when the line after it is empty.

BeforeNonBlank (Doc a)

Doc that renders only before nonblank.

Flush (Doc a)

Doc laid out flush to left margin.

BreakingSpace

A space or line break, in context.

AfterBreak Text

Text printed only at start of line.

CarriageReturn

Newline unless we're at start of line.

NewLine

newline.

BlankLines Int

Ensure a number of blank lines.

Concat (Doc a) (Doc a)

Two documents concatenated.

Empty 

Instances

Instances details
Functor Doc 
Instance details

Defined in Text.DocLayout

Methods

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

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

Foldable Doc 
Instance details

Defined in Text.DocLayout

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Doc a -> m #

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

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

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

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

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

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

toList :: Doc a -> [a] #

null :: Doc a -> Bool #

length :: Doc a -> Int #

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

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

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

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

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

Traversable Doc 
Instance details

Defined in Text.DocLayout

Methods

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

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

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

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

TemplateTarget a => FromContext a (Doc a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

ToContext a a => ToContext a (Doc a) Source # 
Instance details

Defined in Text.DocTemplates.Internal

Methods

toContext :: Doc a -> Context a Source #

toVal :: Doc a -> Val a Source #

Eq a => Eq (Doc a) 
Instance details

Defined in Text.DocLayout

Methods

(==) :: Doc a -> Doc a -> Bool #

(/=) :: Doc a -> Doc a -> Bool #

Data a => Data (Doc a) 
Instance details

Defined in Text.DocLayout

Methods

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

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

toConstr :: Doc a -> Constr #

dataTypeOf :: Doc a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Doc a) 
Instance details

Defined in Text.DocLayout

Methods

compare :: Doc a -> Doc a -> Ordering #

(<) :: Doc a -> Doc a -> Bool #

(<=) :: Doc a -> Doc a -> Bool #

(>) :: Doc a -> Doc a -> Bool #

(>=) :: Doc a -> Doc a -> Bool #

max :: Doc a -> Doc a -> Doc a #

min :: Doc a -> Doc a -> Doc a #

Read a => Read (Doc a) 
Instance details

Defined in Text.DocLayout

Show a => Show (Doc a) 
Instance details

Defined in Text.DocLayout

Methods

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

show :: Doc a -> String #

showList :: [Doc a] -> ShowS #

HasChars a => IsString (Doc a) 
Instance details

Defined in Text.DocLayout

Methods

fromString :: String -> Doc a #

Generic (Doc a) 
Instance details

Defined in Text.DocLayout

Associated Types

type Rep (Doc a) :: Type -> Type #

Methods

from :: Doc a -> Rep (Doc a) x #

to :: Rep (Doc a) x -> Doc a #

Semigroup (Doc a) 
Instance details

Defined in Text.DocLayout

Methods

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

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

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

Monoid (Doc a) 
Instance details

Defined in Text.DocLayout

Methods

mempty :: Doc a #

mappend :: Doc a -> Doc a -> Doc a #

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

type Rep (Doc a) 
Instance details

Defined in Text.DocLayout

type Rep (Doc a) = D1 ('MetaData "Doc" "Text.DocLayout" "doclayout-0.3.0.2-H1fAdBkp6omHBy81ZW4gpC" 'False) (((C1 ('MetaCons "Text" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: (C1 ('MetaCons "Block" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])) :+: C1 ('MetaCons "VFill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) :+: (C1 ('MetaCons "Prefixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a))) :+: (C1 ('MetaCons "BeforeNonBlank" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a))) :+: C1 ('MetaCons "Flush" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)))))) :+: ((C1 ('MetaCons "BreakingSpace" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AfterBreak" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CarriageReturn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NewLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlankLines" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "Concat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a))) :+: C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type)))))