pandoc-types-1.17.6.1: Types for representing a structured document

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

Text.Pandoc.Definition

Description

Definition of Pandoc data structure for format-neutral representation of documents.

Synopsis

Documentation

data Pandoc Source #

Constructors

Pandoc Meta [Block] 
Instances
Eq Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Pandoc -> Pandoc -> Bool #

(/=) :: Pandoc -> Pandoc -> Bool #

Data Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Pandoc -> Constr #

dataTypeOf :: Pandoc -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Read Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Show Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Pandoc :: Type -> Type #

Methods

from :: Pandoc -> Rep Pandoc x #

to :: Rep Pandoc x -> Pandoc #

Semigroup Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Monoid Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Arbitrary Pandoc Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Pandoc -> () #

HasMeta Pandoc Source # 
Instance details

Defined in Text.Pandoc.Builder

Walkable Inline Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Pandoc -> m Pandoc Source #

query :: Monoid c => (Inline -> c) -> Pandoc -> c Source #

Walkable Block Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Pandoc -> m Pandoc Source #

query :: Monoid c => (Block -> c) -> Pandoc -> c Source #

Walkable Pandoc Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Pandoc -> Pandoc) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc Source #

query :: Monoid c => (Pandoc -> c) -> Pandoc -> c Source #

Walkable [Inline] Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Pandoc -> m Pandoc Source #

query :: Monoid c => ([Inline] -> c) -> Pandoc -> c Source #

Walkable [Block] Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Pandoc -> m Pandoc Source #

query :: Monoid c => ([Block] -> c) -> Pandoc -> c Source #

type Rep Pandoc Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep Pandoc = D1 (MetaData "Pandoc" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) (C1 (MetaCons "Pandoc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Meta) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])))

newtype Meta Source #

Metadata for the document: title, authors, date.

Constructors

Meta 
Instances
Eq Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Meta -> Meta -> Bool #

(/=) :: Meta -> Meta -> Bool #

Data Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Meta -> Constr #

dataTypeOf :: Meta -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

compare :: Meta -> Meta -> Ordering #

(<) :: Meta -> Meta -> Bool #

(<=) :: Meta -> Meta -> Bool #

(>) :: Meta -> Meta -> Bool #

(>=) :: Meta -> Meta -> Bool #

max :: Meta -> Meta -> Meta #

min :: Meta -> Meta -> Meta #

Read Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Show Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #

Generic Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Meta :: Type -> Type #

Methods

from :: Meta -> Rep Meta x #

to :: Rep Meta x -> Meta #

Semigroup Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

(<>) :: Meta -> Meta -> Meta #

sconcat :: NonEmpty Meta -> Meta #

stimes :: Integral b => b -> Meta -> Meta #

Monoid Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

mempty :: Meta #

mappend :: Meta -> Meta -> Meta #

mconcat :: [Meta] -> Meta #

Arbitrary Meta Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

Methods

arbitrary :: Gen Meta #

shrink :: Meta -> [Meta] #

ToJSON Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Meta -> () #

HasMeta Meta Source # 
Instance details

Defined in Text.Pandoc.Builder

Walkable Inline Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Meta -> m Meta Source #

query :: Monoid c => (Inline -> c) -> Meta -> c Source #

Walkable Block Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Meta -> m Meta Source #

query :: Monoid c => (Block -> c) -> Meta -> c Source #

Walkable Meta Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Meta -> Meta) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => (Meta -> m Meta) -> Meta -> m Meta Source #

query :: Monoid c => (Meta -> c) -> Meta -> c Source #

Walkable [Inline] Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Meta -> m Meta Source #

query :: Monoid c => ([Inline] -> c) -> Meta -> c Source #

Walkable [Block] Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Meta -> m Meta Source #

query :: Monoid c => ([Block] -> c) -> Meta -> c Source #

type Rep Meta Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep Meta = D1 (MetaData "Meta" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" True) (C1 (MetaCons "Meta" PrefixI True) (S1 (MetaSel (Just "unMeta") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String MetaValue))))

data MetaValue Source #

Instances
Eq MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

Data MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: MetaValue -> Constr #

dataTypeOf :: MetaValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

Read MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

Show MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep MetaValue :: Type -> Type #

ToJSON MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: MetaValue -> () #

ToMetaValue MetaValue Source # 
Instance details

Defined in Text.Pandoc.Builder

Walkable Inline MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> MetaValue -> m MetaValue Source #

query :: Monoid c => (Inline -> c) -> MetaValue -> c Source #

Walkable Block MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> MetaValue -> m MetaValue Source #

query :: Monoid c => (Block -> c) -> MetaValue -> c Source #

Walkable [Inline] MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> MetaValue -> m MetaValue Source #

query :: Monoid c => ([Inline] -> c) -> MetaValue -> c Source #

Walkable [Block] MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> MetaValue -> m MetaValue Source #

query :: Monoid c => ([Block] -> c) -> MetaValue -> c Source #

type Rep MetaValue Source # 
Instance details

Defined in Text.Pandoc.Definition

lookupMeta :: String -> Meta -> Maybe MetaValue Source #

Retrieve the metadata value for a given key.

docTitle :: Meta -> [Inline] Source #

Extract document title from metadata; works just like the old docTitle.

docAuthors :: Meta -> [[Inline]] Source #

Extract document authors from metadata; works just like the old docAuthors.

docDate :: Meta -> [Inline] Source #

Extract date from metadata; works just like the old docDate.

data Block Source #

Block element.

Constructors

Plain [Inline]

Plain text, not a paragraph

Para [Inline]

Paragraph

LineBlock [[Inline]]

Multiple non-breaking lines

CodeBlock Attr String

Code block (literal) with attributes

RawBlock Format String

Raw block

BlockQuote [Block]

Block quote (list of blocks)

OrderedList ListAttributes [[Block]]

Ordered list (attributes and a list of items, each a list of blocks)

BulletList [[Block]]

Bullet list (list of items, each a list of blocks)

DefinitionList [([Inline], [[Block]])]

Definition list Each list item is a pair consisting of a term (a list of inlines) and one or more definitions (each a list of blocks)

Header Int Attr [Inline]

Header - level (integer) and text (inlines)

HorizontalRule

Horizontal rule

Table [Inline] [Alignment] [Double] [TableCell] [[TableCell]]

Table, with caption, column alignments (required), relative column widths (0 = default), column headers (each a list of blocks), and rows (each a list of lists of blocks)

Div Attr [Block]

Generic block container with attributes

Null

Nothing

Instances
Eq Block Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Block -> Block -> Bool #

(/=) :: Block -> Block -> Bool #

Data Block Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Block -> Constr #

dataTypeOf :: Block -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Block Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

compare :: Block -> Block -> Ordering #

(<) :: Block -> Block -> Bool #

(<=) :: Block -> Block -> Bool #

(>) :: Block -> Block -> Bool #

(>=) :: Block -> Block -> Bool #

max :: Block -> Block -> Block #

min :: Block -> Block -> Block #

Read Block Source # 
Instance details

Defined in Text.Pandoc.Definition

Show Block Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

Arbitrary Block Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

Methods

arbitrary :: Gen Block #

shrink :: Block -> [Block] #

Arbitrary Blocks Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON Block Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Block Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData Block Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Block -> () #

ToMetaValue Blocks Source # 
Instance details

Defined in Text.Pandoc.Builder

Walkable Inline Block Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Block -> Block Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Block -> m Block Source #

query :: Monoid c => (Inline -> c) -> Block -> c Source #

Walkable Block Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Citation -> m Citation Source #

query :: Monoid c => (Block -> c) -> Citation -> c Source #

Walkable Block Inline Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Inline -> Inline Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Inline -> m Inline Source #

query :: Monoid c => (Block -> c) -> Inline -> c Source #

Walkable Block Block Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Block -> Block Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Block -> m Block Source #

query :: Monoid c => (Block -> c) -> Block -> c Source #

Walkable Block MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> MetaValue -> m MetaValue Source #

query :: Monoid c => (Block -> c) -> MetaValue -> c Source #

Walkable Block Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Meta -> m Meta Source #

query :: Monoid c => (Block -> c) -> Meta -> c Source #

Walkable Block Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Pandoc -> m Pandoc Source #

query :: Monoid c => (Block -> c) -> Pandoc -> c Source #

Semigroup (Many Block) Source # 
Instance details

Defined in Text.Pandoc.Builder

Monoid (Many Block) Source # 
Instance details

Defined in Text.Pandoc.Builder

Walkable [Inline] Block Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Block -> Block Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Block -> m Block Source #

query :: Monoid c => ([Inline] -> c) -> Block -> c Source #

Walkable [Block] Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Citation -> m Citation Source #

query :: Monoid c => ([Block] -> c) -> Citation -> c Source #

Walkable [Block] Inline Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Inline -> Inline Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Inline -> m Inline Source #

query :: Monoid c => ([Block] -> c) -> Inline -> c Source #

Walkable [Block] Block Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Block -> Block Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Block -> m Block Source #

query :: Monoid c => ([Block] -> c) -> Block -> c Source #

Walkable [Block] MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> MetaValue -> m MetaValue Source #

query :: Monoid c => ([Block] -> c) -> MetaValue -> c Source #

Walkable [Block] Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Meta -> m Meta Source #

query :: Monoid c => ([Block] -> c) -> Meta -> c Source #

Walkable [Block] Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Pandoc -> m Pandoc Source #

query :: Monoid c => ([Block] -> c) -> Pandoc -> c Source #

Walkable [Block] [Block] Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> [Block] -> [Block] Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> [Block] -> m [Block] Source #

query :: Monoid c => ([Block] -> c) -> [Block] -> c Source #

type Rep Block Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep Block = D1 (MetaData "Block" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) (((C1 (MetaCons "Plain" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: (C1 (MetaCons "Para" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "LineBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Inline]])))) :+: ((C1 (MetaCons "CodeBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "RawBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Format) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) :+: (C1 (MetaCons "BlockQuote" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "OrderedList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ListAttributes) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Block]]))))) :+: ((C1 (MetaCons "BulletList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Block]])) :+: (C1 (MetaCons "DefinitionList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [([Inline], [[Block]])])) :+: C1 (MetaCons "Header" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]))))) :+: ((C1 (MetaCons "HorizontalRule" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Table" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Alignment])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Double]) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TableCell]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[TableCell]]))))) :+: (C1 (MetaCons "Div" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "Null" PrefixI False) (U1 :: Type -> Type)))))

data Inline Source #

Inline elements.

Constructors

Str String

Text (string)

Emph [Inline]

Emphasized text (list of inlines)

Strong [Inline]

Strongly emphasized text (list of inlines)

Strikeout [Inline]

Strikeout text (list of inlines)

Superscript [Inline]

Superscripted text (list of inlines)

Subscript [Inline]

Subscripted text (list of inlines)

SmallCaps [Inline]

Small caps text (list of inlines)

Quoted QuoteType [Inline]

Quoted text (list of inlines)

Cite [Citation] [Inline]

Citation (list of inlines)

Code Attr String

Inline code (literal)

Space

Inter-word space

SoftBreak

Soft line break

LineBreak

Hard line break

Math MathType String

TeX math (literal)

RawInline Format String

Raw inline

Link Attr [Inline] Target

Hyperlink: alt text (list of inlines), target

Image Attr [Inline] Target

Image: alt text (list of inlines), target

Note [Block]

Footnote or endnote

Span Attr [Inline]

Generic inline container with attributes

Instances
Eq Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Inline -> Inline -> Bool #

(/=) :: Inline -> Inline -> Bool #

Data Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Inline -> Constr #

dataTypeOf :: Inline -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

Read Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

Show Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

IsString Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

fromString :: String -> Inlines #

Generic Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Semigroup Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Monoid Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Arbitrary Inline Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

Arbitrary Inlines Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Inline -> () #

ToMetaValue Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Walkable Inline Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Citation -> m Citation Source #

query :: Monoid c => (Inline -> c) -> Citation -> c Source #

Walkable Inline Inline Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Inline -> Inline Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Inline -> m Inline Source #

query :: Monoid c => (Inline -> c) -> Inline -> c Source #

Walkable Inline Block Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Block -> Block Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Block -> m Block Source #

query :: Monoid c => (Inline -> c) -> Block -> c Source #

Walkable Inline MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> MetaValue -> m MetaValue Source #

query :: Monoid c => (Inline -> c) -> MetaValue -> c Source #

Walkable Inline Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Meta -> m Meta Source #

query :: Monoid c => (Inline -> c) -> Meta -> c Source #

Walkable Inline Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Pandoc -> m Pandoc Source #

query :: Monoid c => (Inline -> c) -> Pandoc -> c Source #

Walkable Block Inline Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Inline -> Inline Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Inline -> m Inline Source #

query :: Monoid c => (Block -> c) -> Inline -> c Source #

Walkable [Inline] Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Citation -> m Citation Source #

query :: Monoid c => ([Inline] -> c) -> Citation -> c Source #

Walkable [Inline] Inline Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Inline -> Inline Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Inline -> m Inline Source #

query :: Monoid c => ([Inline] -> c) -> Inline -> c Source #

Walkable [Inline] Block Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Block -> Block Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Block -> m Block Source #

query :: Monoid c => ([Inline] -> c) -> Block -> c Source #

Walkable [Inline] MetaValue Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> MetaValue -> MetaValue Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> MetaValue -> m MetaValue Source #

query :: Monoid c => ([Inline] -> c) -> MetaValue -> c Source #

Walkable [Inline] Meta Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Meta -> Meta Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Meta -> m Meta Source #

query :: Monoid c => ([Inline] -> c) -> Meta -> c Source #

Walkable [Inline] Pandoc Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Pandoc -> Pandoc Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Pandoc -> m Pandoc Source #

query :: Monoid c => ([Inline] -> c) -> Pandoc -> c Source #

Walkable [Block] Inline Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Inline -> Inline Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Inline -> m Inline Source #

query :: Monoid c => ([Block] -> c) -> Inline -> c Source #

Walkable [Inline] [Inline] Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> [Inline] -> [Inline] Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> [Inline] -> m [Inline] Source #

query :: Monoid c => ([Inline] -> c) -> [Inline] -> c Source #

type Rep Inline Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep Inline = D1 (MetaData "Inline" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) ((((C1 (MetaCons "Str" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "Emph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]))) :+: (C1 (MetaCons "Strong" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "Strikeout" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])))) :+: ((C1 (MetaCons "Superscript" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "Subscript" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]))) :+: (C1 (MetaCons "SmallCaps" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: (C1 (MetaCons "Quoted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QuoteType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "Cite" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Citation]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])))))) :+: (((C1 (MetaCons "Code" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "Space" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SoftBreak" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LineBreak" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Math" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MathType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) :+: ((C1 (MetaCons "RawInline" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Format) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "Link" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Target)))) :+: (C1 (MetaCons "Image" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Target))) :+: (C1 (MetaCons "Note" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "Span" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])))))))

data Alignment Source #

Alignment of a table column.

Instances
Eq Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

Data Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Alignment -> Constr #

dataTypeOf :: Alignment -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

Read Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

Show Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Alignment :: Type -> Type #

Arbitrary Alignment Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Alignment -> () #

type Rep Alignment Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep Alignment = D1 (MetaData "Alignment" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) ((C1 (MetaCons "AlignLeft" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignRight" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AlignCenter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignDefault" PrefixI False) (U1 :: Type -> Type)))

type ListAttributes = (Int, ListNumberStyle, ListNumberDelim) Source #

List attributes. The first element of the triple is the start number of the list.

data ListNumberStyle Source #

Style of list numbers.

Instances
Eq ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

Data ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: ListNumberStyle -> Constr #

dataTypeOf :: ListNumberStyle -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

Read ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

Show ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep ListNumberStyle :: Type -> Type #

Arbitrary ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: ListNumberStyle -> () #

type Rep ListNumberStyle Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep ListNumberStyle = D1 (MetaData "ListNumberStyle" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) ((C1 (MetaCons "DefaultStyle" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Example" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Decimal" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LowerRoman" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UpperRoman" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LowerAlpha" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UpperAlpha" PrefixI False) (U1 :: Type -> Type))))

data ListNumberDelim Source #

Delimiter of list numbers.

Instances
Eq ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

Data ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: ListNumberDelim -> Constr #

dataTypeOf :: ListNumberDelim -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

Read ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

Show ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep ListNumberDelim :: Type -> Type #

Arbitrary ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: ListNumberDelim -> () #

type Rep ListNumberDelim Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep ListNumberDelim = D1 (MetaData "ListNumberDelim" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) ((C1 (MetaCons "DefaultDelim" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Period" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OneParen" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TwoParens" PrefixI False) (U1 :: Type -> Type)))

newtype Format Source #

Formats for raw blocks

Constructors

Format String 
Instances
Eq Format Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Data Format Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Format -> Constr #

dataTypeOf :: Format -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Format Source # 
Instance details

Defined in Text.Pandoc.Definition

Read Format Source # 
Instance details

Defined in Text.Pandoc.Definition

Show Format Source # 
Instance details

Defined in Text.Pandoc.Definition

IsString Format Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

fromString :: String -> Format #

Generic Format Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Format :: Type -> Type #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

ToJSON Format Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Format Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData Format Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Format -> () #

ToJSONFilter a => ToJSONFilter (Maybe Format -> a) Source # 
Instance details

Defined in Text.Pandoc.JSON

Methods

toJSONFilter :: (Maybe Format -> a) -> IO () Source #

type Rep Format Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep Format = D1 (MetaData "Format" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" True) (C1 (MetaCons "Format" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

type Attr = (String, [String], [(String, String)]) Source #

Attributes: identifier, classes, key-value pairs

type TableCell = [Block] Source #

Table cells are list of Blocks

data QuoteType Source #

Type of quotation marks to use in Quoted inline.

Constructors

SingleQuote 
DoubleQuote 
Instances
Eq QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

Data QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: QuoteType -> Constr #

dataTypeOf :: QuoteType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

Read QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

Show QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep QuoteType :: Type -> Type #

Arbitrary QuoteType Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: QuoteType -> () #

type Rep QuoteType Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep QuoteType = D1 (MetaData "QuoteType" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) (C1 (MetaCons "SingleQuote" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DoubleQuote" PrefixI False) (U1 :: Type -> Type))

type Target = (String, String) Source #

Link target (URL, title).

data MathType Source #

Type of math element (display or inline).

Constructors

DisplayMath 
InlineMath 
Instances
Eq MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

Data MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: MathType -> Constr #

dataTypeOf :: MathType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

Read MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

Show MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep MathType :: Type -> Type #

Methods

from :: MathType -> Rep MathType x #

to :: Rep MathType x -> MathType #

Arbitrary MathType Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: MathType -> () #

type Rep MathType Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep MathType = D1 (MetaData "MathType" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) (C1 (MetaCons "DisplayMath" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InlineMath" PrefixI False) (U1 :: Type -> Type))

data Citation Source #

Instances
Eq Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

Data Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Citation -> Constr #

dataTypeOf :: Citation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

Read Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

Show Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Citation :: Type -> Type #

Methods

from :: Citation -> Rep Citation x #

to :: Rep Citation x -> Citation #

Arbitrary Citation Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Citation -> () #

Walkable Inline Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Citation -> m Citation Source #

query :: Monoid c => (Inline -> c) -> Citation -> c Source #

Walkable Block Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Citation -> m Citation Source #

query :: Monoid c => (Block -> c) -> Citation -> c Source #

Walkable [Inline] Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Citation -> m Citation Source #

query :: Monoid c => ([Inline] -> c) -> Citation -> c Source #

Walkable [Block] Citation Source # 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Citation -> Citation Source #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Citation -> m Citation Source #

query :: Monoid c => ([Block] -> c) -> Citation -> c Source #

type Rep Citation Source # 
Instance details

Defined in Text.Pandoc.Definition

data CitationMode Source #

Instances
Eq CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

Data CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: CitationMode -> Constr #

dataTypeOf :: CitationMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

Read CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

Show CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

Generic CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep CitationMode :: Type -> Type #

Arbitrary CitationMode Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToJSON CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

FromJSON CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

NFData CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: CitationMode -> () #

type Rep CitationMode Source # 
Instance details

Defined in Text.Pandoc.Definition

type Rep CitationMode = D1 (MetaData "CitationMode" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) (C1 (MetaCons "AuthorInText" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SuppressAuthor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NormalCitation" PrefixI False) (U1 :: Type -> Type)))