Copyright | Copyright (C) 2009-2020 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Text.Pandoc.Templates
Description
Utility functions for working with pandoc templates.
Synopsis
- data Template a
- newtype WithDefaultPartials m a = WithDefaultPartials {
- runWithDefaultPartials :: m a
- newtype WithPartials m a = WithPartials {
- runWithPartials :: m a
- compileTemplate :: (TemplateMonad m, TemplateTarget a) => FilePath -> Text -> m (Either String (Template a))
- renderTemplate :: (TemplateTarget a, ToContext a b) => Template a -> b -> Doc a
- getTemplate :: PandocMonad m => FilePath -> m Text
- getDefaultTemplate :: PandocMonad m => Text -> m Text
- compileDefaultTemplate :: PandocMonad m => Text -> m (Template Text)
Documentation
A template.
Instances
Functor Template | |
Foldable Template | |
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 elem :: Eq a => a -> Template a -> Bool maximum :: Ord a => Template a -> a minimum :: Ord a => Template a -> a | |
Traversable Template | |
Eq a => Eq (Template a) | |
Data a => Data (Template a) | |
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) | |
Defined in Text.DocTemplates.Internal | |
Read a => Read (Template a) | |
Show a => Show (Template a) | |
Generic (Template a) | |
Semigroup a => Semigroup (Template a) | |
Semigroup a => Monoid (Template a) | |
type Rep (Template a) | |
Defined in Text.DocTemplates.Internal type Rep (Template a) = D1 ('MetaData "Template" "Text.DocTemplates.Internal" "doctemplates-0.8.2-5rbdVp4eyzEEVaVPUXCx20" '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)))) |
newtype WithDefaultPartials m a Source #
Wrap a Monad in this if you want partials to be taken only from the default data files.
Constructors
WithDefaultPartials | |
Fields
|
Instances
newtype WithPartials m a Source #
Wrap a Monad in this if you want partials to be looked for locally (or, when the main template is at a URL, via HTTP), falling back to default data files.
Constructors
WithPartials | |
Fields
|
Instances
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.
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.
getTemplate :: PandocMonad m => FilePath -> m Text Source #
Retrieve text for a template.
Arguments
:: PandocMonad m | |
=> Text | Name of writer |
-> m Text |
Get default template for the specified writer.
compileDefaultTemplate :: PandocMonad m => Text -> m (Template Text) Source #
Get and compile default template for the specified writer. Raise an error on compilation failure.