Copyright | Copyright (C) 2006-2023 John MacFarlane |
---|---|
License | BSD3 |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Definition of Pandoc
data structure for format-neutral representation
of documents.
Synopsis
- data Pandoc = Pandoc Meta [Block]
- newtype Meta = Meta {}
- data MetaValue
- = MetaMap (Map Text MetaValue)
- | MetaList [MetaValue]
- | MetaBool Bool
- | MetaString Text
- | MetaInlines [Inline]
- | MetaBlocks [Block]
- nullMeta :: Meta
- isNullMeta :: Meta -> Bool
- lookupMeta :: Text -> Meta -> Maybe MetaValue
- docTitle :: Meta -> [Inline]
- docAuthors :: Meta -> [[Inline]]
- docDate :: Meta -> [Inline]
- data Block
- = Plain [Inline]
- | Para [Inline]
- | LineBlock [[Inline]]
- | CodeBlock Attr Text
- | RawBlock Format Text
- | BlockQuote [Block]
- | OrderedList ListAttributes [[Block]]
- | BulletList [[Block]]
- | DefinitionList [([Inline], [[Block]])]
- | Header Int Attr [Inline]
- | HorizontalRule
- | Table Attr Caption [ColSpec] TableHead [TableBody] TableFoot
- | Figure Attr Caption [Block]
- | Div Attr [Block]
- pattern SimpleFigure :: Attr -> [Inline] -> Target -> Block
- data Inline
- = Str Text
- | Emph [Inline]
- | Underline [Inline]
- | Strong [Inline]
- | Strikeout [Inline]
- | Superscript [Inline]
- | Subscript [Inline]
- | SmallCaps [Inline]
- | Quoted QuoteType [Inline]
- | Cite [Citation] [Inline]
- | Code Attr Text
- | Space
- | SoftBreak
- | LineBreak
- | Math MathType Text
- | RawInline Format Text
- | Link Attr [Inline] Target
- | Image Attr [Inline] Target
- | Note [Block]
- | Span Attr [Inline]
- type ListAttributes = (Int, ListNumberStyle, ListNumberDelim)
- data ListNumberStyle
- data ListNumberDelim
- newtype Format = Format Text
- type Attr = (Text, [Text], [(Text, Text)])
- nullAttr :: Attr
- data Caption = Caption (Maybe ShortCaption) [Block]
- type ShortCaption = [Inline]
- newtype RowHeadColumns = RowHeadColumns Int
- data Alignment
- data ColWidth
- type ColSpec = (Alignment, ColWidth)
- data Row = Row Attr [Cell]
- data TableHead = TableHead Attr [Row]
- data TableBody = TableBody Attr RowHeadColumns [Row] [Row]
- data TableFoot = TableFoot Attr [Row]
- data Cell = Cell Attr Alignment RowSpan ColSpan [Block]
- newtype RowSpan = RowSpan Int
- newtype ColSpan = ColSpan Int
- data QuoteType
- type Target = (Text, Text)
- data MathType
- data Citation = Citation {
- citationId :: Text
- citationPrefix :: [Inline]
- citationSuffix :: [Inline]
- citationMode :: CitationMode
- citationNoteNum :: Int
- citationHash :: Int
- data CitationMode
- pandocTypesVersion :: Version
Documentation
Instances
Metadata for the document: title, authors, date.
Instances
Arbitrary Meta Source # | |
FromJSON Meta Source # | |
ToJSON Meta Source # | |
Defined in Text.Pandoc.Definition | |
Data Meta Source # | |
Defined in Text.Pandoc.Definition 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 # 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 :: forall r r'. (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 # | |
Monoid Meta Source # | |
Semigroup Meta Source # | |
Generic Meta Source # | |
Read Meta Source # | |
Show Meta Source # | |
NFData Meta Source # | |
Defined in Text.Pandoc.Definition | |
Eq Meta Source # | |
Ord Meta Source # | |
HasMeta Meta Source # | |
Defined in Text.Pandoc.Builder | |
Walkable Block Meta Source # | |
Walkable Inline Meta Source # | |
Walkable Meta Meta Source # | |
Walkable Meta Pandoc Source # | |
Walkable MetaValue Meta Source # | |
Walkable [Block] Meta Source # | |
Walkable [Inline] Meta Source # | |
type Rep Meta Source # | |
Defined in Text.Pandoc.Definition |
MetaMap (Map Text MetaValue) | |
MetaList [MetaValue] | |
MetaBool Bool | |
MetaString Text | |
MetaInlines [Inline] | |
MetaBlocks [Block] |
Instances
isNullMeta :: Meta -> Bool Source #
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
.
Block element.
Plain [Inline] | Plain text, not a paragraph |
Para [Inline] | Paragraph |
LineBlock [[Inline]] | Multiple non-breaking lines |
CodeBlock Attr Text | Code block (literal) with attributes |
RawBlock Format Text | 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 Attr Caption [ColSpec] TableHead [TableBody] TableFoot | Table, with attributes, caption, optional short caption, column alignments and widths (required), table head, table bodies, and table foot |
Figure Attr Caption [Block] | Figure, with attributes, caption, and content (list of blocks) |
Div Attr [Block] | Generic block container with attributes |
Instances
pattern SimpleFigure :: Attr -> [Inline] -> Target -> Block Source #
Bidirectional patter synonym
It can pass as a Block constructor
>>>
SimpleFigure nullAttr [] (T.pack "", T.pack "title")
Para [Image ("",[],[]) [] ("","fig:title")]
It can be used to pattern match >>> let img = Para [Image undefined undefined (undefined, T.pack "title")] >>> case img of { SimpleFigure _ _ _ -> True; _ -> False } False >>> let fig = Para [Image undefined undefined (undefined, T.pack "fig:title")] >>> case fig of { SimpleFigure _ _ tit -> snd tit; _ -> T.pack "" } "title"
Inline elements.
Str Text | Text (string) |
Emph [Inline] | Emphasized text (list of inlines) |
Underline [Inline] | Underlined 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 Text | Inline code (literal) |
Space | Inter-word space |
SoftBreak | Soft line break |
LineBreak | Hard line break |
Math MathType Text | TeX math (literal) |
RawInline Format Text | 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
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
data ListNumberDelim Source #
Delimiter of list numbers.
Instances
Formats for raw blocks
Instances
FromJSON Format Source # | |
ToJSON Format Source # | |
Defined in Text.Pandoc.Definition | |
Data Format Source # | |
Defined in Text.Pandoc.Definition 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 :: forall r r'. (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 # | |
IsString Format Source # | |
Defined in Text.Pandoc.Definition fromString :: String -> Format # | |
Generic Format Source # | |
Read Format Source # | |
Show Format Source # | |
NFData Format Source # | |
Defined in Text.Pandoc.Definition | |
Eq Format Source # | |
Ord Format Source # | |
(ToJSONFilter m a, MonadIO m) => ToJSONFilter m (Maybe Format -> a) Source # | |
Defined in Text.Pandoc.JSON toJSONFilter :: (Maybe Format -> a) -> m () Source # | |
type Rep Format Source # | |
Defined in Text.Pandoc.Definition |
The caption of a table or figure, with optional short caption.
Instances
type ShortCaption = [Inline] Source #
A short caption, for use in, for instance, lists of figures.
newtype RowHeadColumns Source #
The number of columns taken up by the row head of each row of a
TableBody
. The row body takes up the remaining columns.
Instances
Alignment of a table column.
Instances
Arbitrary Alignment Source # | |
FromJSON Alignment Source # | |
ToJSON Alignment Source # | |
Defined in Text.Pandoc.Definition | |
Data Alignment Source # | |
Defined in Text.Pandoc.Definition 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 :: forall r r'. (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 # | |
Generic Alignment Source # | |
Read Alignment Source # | |
Show Alignment Source # | |
NFData Alignment Source # | |
Defined in Text.Pandoc.Definition | |
Eq Alignment Source # | |
Ord Alignment Source # | |
Defined in Text.Pandoc.Definition | |
type Rep Alignment Source # | |
Defined in Text.Pandoc.Definition type Rep Alignment = D1 ('MetaData "Alignment" "Text.Pandoc.Definition" "pandoc-types-1.23.0.1-LvFM57g4V0qGOnWGZwYMk2" '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))) |
The width of a table column, as a percentage of the text width.
Instances
FromJSON ColWidth Source # | |
ToJSON ColWidth Source # | |
Defined in Text.Pandoc.Definition | |
Data ColWidth Source # | |
Defined in Text.Pandoc.Definition gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColWidth -> c ColWidth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColWidth # toConstr :: ColWidth -> Constr # dataTypeOf :: ColWidth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColWidth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth) # gmapT :: (forall b. Data b => b -> b) -> ColWidth -> ColWidth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r # gmapQ :: (forall d. Data d => d -> u) -> ColWidth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ColWidth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth # | |
Generic ColWidth Source # | |
Read ColWidth Source # | |
Show ColWidth Source # | |
NFData ColWidth Source # | |
Defined in Text.Pandoc.Definition | |
Eq ColWidth Source # | |
Ord ColWidth Source # | |
Defined in Text.Pandoc.Definition | |
type Rep ColWidth Source # | |
Defined in Text.Pandoc.Definition type Rep ColWidth = D1 ('MetaData "ColWidth" "Text.Pandoc.Definition" "pandoc-types-1.23.0.1-LvFM57g4V0qGOnWGZwYMk2" 'False) (C1 ('MetaCons "ColWidth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "ColWidthDefault" 'PrefixI 'False) (U1 :: Type -> Type)) |
A table row.
Instances
Arbitrary Row Source # | |
FromJSON Row Source # | |
ToJSON Row Source # | |
Defined in Text.Pandoc.Definition | |
Data Row Source # | |
Defined in Text.Pandoc.Definition gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Row -> c Row # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Row # dataTypeOf :: Row -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Row) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row) # gmapT :: (forall b. Data b => b -> b) -> Row -> Row # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r # gmapQ :: (forall d. Data d => d -> u) -> Row -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Row -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Row -> m Row # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row # | |
Generic Row Source # | |
Read Row Source # | |
Show Row Source # | |
NFData Row Source # | |
Defined in Text.Pandoc.Definition | |
Eq Row Source # | |
Ord Row Source # | |
Walkable Block Row Source # | |
Walkable Inline Row Source # | |
Walkable [Block] Row Source # | |
Walkable [Inline] Row Source # | |
type Rep Row Source # | |
Defined in Text.Pandoc.Definition type Rep Row = D1 ('MetaData "Row" "Text.Pandoc.Definition" "pandoc-types-1.23.0.1-LvFM57g4V0qGOnWGZwYMk2" 'False) (C1 ('MetaCons "Row" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Cell]))) |
The head of a table.
Instances
A body of a table, with an intermediate head, intermediate body, and the specified number of row header columns in the intermediate body.
Instances
The foot of a table.
Instances
A table cell.
Instances
The number of rows occupied by a cell; the height of a cell.
Instances
FromJSON RowSpan Source # | |
ToJSON RowSpan Source # | |
Defined in Text.Pandoc.Definition | |
Data RowSpan Source # | |
Defined in Text.Pandoc.Definition gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowSpan -> c RowSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowSpan # toConstr :: RowSpan -> Constr # dataTypeOf :: RowSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan) # gmapT :: (forall b. Data b => b -> b) -> RowSpan -> RowSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> RowSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RowSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan # | |
Enum RowSpan Source # | |
Generic RowSpan Source # | |
Num RowSpan Source # | |
Read RowSpan Source # | |
Show RowSpan Source # | |
NFData RowSpan Source # | |
Defined in Text.Pandoc.Definition | |
Eq RowSpan Source # | |
Ord RowSpan Source # | |
type Rep RowSpan Source # | |
Defined in Text.Pandoc.Definition |
The number of columns occupied by a cell; the width of a cell.
Instances
FromJSON ColSpan Source # | |
ToJSON ColSpan Source # | |
Defined in Text.Pandoc.Definition | |
Data ColSpan Source # | |
Defined in Text.Pandoc.Definition gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColSpan -> c ColSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColSpan # toConstr :: ColSpan -> Constr # dataTypeOf :: ColSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan) # gmapT :: (forall b. Data b => b -> b) -> ColSpan -> ColSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> ColSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ColSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan # | |
Enum ColSpan Source # | |
Generic ColSpan Source # | |
Num ColSpan Source # | |
Read ColSpan Source # | |
Show ColSpan Source # | |
NFData ColSpan Source # | |
Defined in Text.Pandoc.Definition | |
Eq ColSpan Source # | |
Ord ColSpan Source # | |
type Rep ColSpan Source # | |
Defined in Text.Pandoc.Definition |
Type of quotation marks to use in Quoted inline.
Instances
Arbitrary QuoteType Source # | |
FromJSON QuoteType Source # | |
ToJSON QuoteType Source # | |
Defined in Text.Pandoc.Definition | |
Data QuoteType Source # | |
Defined in Text.Pandoc.Definition 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 :: forall r r'. (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 # | |
Generic QuoteType Source # | |
Read QuoteType Source # | |
Show QuoteType Source # | |
NFData QuoteType Source # | |
Defined in Text.Pandoc.Definition | |
Eq QuoteType Source # | |
Ord QuoteType Source # | |
Defined in Text.Pandoc.Definition | |
type Rep QuoteType Source # | |
Type of math element (display or inline).
Instances
Arbitrary MathType Source # | |
FromJSON MathType Source # | |
ToJSON MathType Source # | |
Defined in Text.Pandoc.Definition | |
Data MathType Source # | |
Defined in Text.Pandoc.Definition 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 :: forall r r'. (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 # | |
Generic MathType Source # | |
Read MathType Source # | |
Show MathType Source # | |
NFData MathType Source # | |
Defined in Text.Pandoc.Definition | |
Eq MathType Source # | |
Ord MathType Source # | |
Defined in Text.Pandoc.Definition | |
type Rep MathType Source # | |
Citation | |
|
Instances
data CitationMode Source #