pandoc-3.1.13: Conversion between markup formats
CopyrightCopyright (C) 2009-2023 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Pandoc.Templates

Description

Utility functions for working with pandoc templates.

WithDefaultPartials and WithPartials are Monad wrappers. Wrapping these around an instance of PandocMonad gives different instances of TemplateMonad, with different search behaviors when retrieving partials.

To compile a template and limit partial search to pandoc’s data files, use runWithDefaultPartials (compileTemplate ...).

To compile a template and allow partials to be found locally (either on the file system or via HTTP, in the event that the main template has an absolute URL), ue runWithPartials (compileTemplate ...).

getTemplate seeks a template locally, or via HTTP if the template has an absolute URL, falling back to the data files if not found.

Synopsis

Documentation

data Template a #

A template.

Instances

Instances details
Foldable Template 
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 
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) #

Functor Template 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

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

Semigroup a => Monoid (Template a) 
Instance details

Defined in Text.DocTemplates.Internal

Methods

mempty :: Template a #

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

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

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

Generic (Template a) 
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 #

Read a => Read (Template a) 
Instance details

Defined in Text.DocTemplates.Internal

Show a => Show (Template a) 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

show :: Template a -> String #

showList :: [Template a] -> ShowS #

Eq a => Eq (Template a) 
Instance details

Defined in Text.DocTemplates.Internal

Methods

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

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

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

type Rep (Template a) 
Instance details

Defined in Text.DocTemplates.Internal

type Rep (Template a) = D1 ('MetaData "Template" "Text.DocTemplates.Internal" "doctemplates-0.11-2L7FXTVTtKi8RHIj0bPLm9" '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

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

Instances details
Applicative m => Applicative (WithPartials m) Source # 
Instance details

Defined in Text.Pandoc.Templates

Methods

pure :: a -> WithPartials m a #

(<*>) :: WithPartials m (a -> b) -> WithPartials m a -> WithPartials m b #

liftA2 :: (a -> b -> c) -> WithPartials m a -> WithPartials m b -> WithPartials m c #

(*>) :: WithPartials m a -> WithPartials m b -> WithPartials m b #

(<*) :: WithPartials m a -> WithPartials m b -> WithPartials m a #

Functor m => Functor (WithPartials m) Source # 
Instance details

Defined in Text.Pandoc.Templates

Methods

fmap :: (a -> b) -> WithPartials m a -> WithPartials m b #

(<$) :: a -> WithPartials m b -> WithPartials m a #

Monad m => Monad (WithPartials m) Source # 
Instance details

Defined in Text.Pandoc.Templates

Methods

(>>=) :: WithPartials m a -> (a -> WithPartials m b) -> WithPartials m b #

(>>) :: WithPartials m a -> WithPartials m b -> WithPartials m b #

return :: a -> WithPartials m a #

PandocMonad m => TemplateMonad (WithPartials m) Source # 
Instance details

Defined in Text.Pandoc.Templates

compileTemplate :: (TemplateMonad m, TemplateTarget a) => FilePath -> Text -> m (Either String (Template a)) #

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 #

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.

getDefaultTemplate Source #

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.