| Copyright | Copyright (C) 2006-2019 John MacFarlane | 
|---|---|
| License | BSD3 | 
| Maintainer | John MacFarlane <jgm@berkeley.edu> | 
| Stability | alpha | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Text.Pandoc.Definition
Description
Definition of Pandoc data structure for format-neutral representation
of documents.
Synopsis
- data Pandoc = Pandoc Meta [Block]
 - newtype Meta = Meta {}
 - data MetaValue
- = MetaMap (Map String MetaValue)
 - | MetaList [MetaValue]
 - | MetaBool Bool
 - | MetaString String
 - | MetaInlines [Inline]
 - | MetaBlocks [Block]
 
 - nullMeta :: Meta
 - isNullMeta :: Meta -> Bool
 - lookupMeta :: String -> Meta -> Maybe MetaValue
 - docTitle :: Meta -> [Inline]
 - docAuthors :: Meta -> [[Inline]]
 - docDate :: Meta -> [Inline]
 - data Block
- = Plain [Inline]
 - | Para [Inline]
 - | LineBlock [[Inline]]
 - | CodeBlock Attr String
 - | RawBlock Format String
 - | BlockQuote [Block]
 - | OrderedList ListAttributes [[Block]]
 - | BulletList [[Block]]
 - | DefinitionList [([Inline], [[Block]])]
 - | Header Int Attr [Inline]
 - | HorizontalRule
 - | Table [Inline] [Alignment] [Double] [TableCell] [[TableCell]]
 - | Div Attr [Block]
 - | Null
 
 - data Inline
- = Str String
 - | Emph [Inline]
 - | Strong [Inline]
 - | Strikeout [Inline]
 - | Superscript [Inline]
 - | Subscript [Inline]
 - | SmallCaps [Inline]
 - | Quoted QuoteType [Inline]
 - | Cite [Citation] [Inline]
 - | Code Attr String
 - | Space
 - | SoftBreak
 - | LineBreak
 - | Math MathType String
 - | RawInline Format String
 - | Link Attr [Inline] Target
 - | Image Attr [Inline] Target
 - | Note [Block]
 - | Span Attr [Inline]
 
 - data Alignment
 - type ListAttributes = (Int, ListNumberStyle, ListNumberDelim)
 - data ListNumberStyle
 - data ListNumberDelim
 - newtype Format = Format String
 - type Attr = (String, [String], [(String, String)])
 - nullAttr :: Attr
 - type TableCell = [Block]
 - data QuoteType
 - type Target = (String, String)
 - data MathType
 - data Citation = Citation {}
 - data CitationMode
 - pandocTypesVersion :: Version
 
Documentation
Instances
Metadata for the document: title, authors, date.
Instances
| Eq Meta Source # | |
| Data Meta Source # | |
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 # 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 # | |
| Read Meta Source # | |
| Show Meta Source # | |
| Generic Meta Source # | |
| Semigroup Meta Source # | |
| Monoid Meta Source # | |
| Arbitrary Meta Source # | |
| ToJSON Meta Source # | |
Defined in Text.Pandoc.Definition  | |
| FromJSON Meta Source # | |
| NFData Meta Source # | |
Defined in Text.Pandoc.Definition  | |
| HasMeta Meta Source # | |
Defined in Text.Pandoc.Builder  | |
| Walkable Inline Meta Source # | |
| Walkable Block Meta Source # | |
| Walkable Meta Meta Source # | |
| Walkable [Inline] Meta Source # | |
| Walkable [Block] Meta Source # | |
| type Rep Meta Source # | |
Defined in Text.Pandoc.Definition  | |
Constructors
| MetaMap (Map String MetaValue) | |
| MetaList [MetaValue] | |
| MetaBool Bool | |
| MetaString String | |
| MetaInlines [Inline] | |
| MetaBlocks [Block] | 
Instances
isNullMeta :: Meta -> Bool Source #
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.
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
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
Alignment of a table column.
Constructors
| AlignLeft | |
| AlignRight | |
| AlignCenter | |
| AlignDefault | 
Instances
| Eq Alignment Source # | |
| Data Alignment Source # | |
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 # | |
| Read Alignment Source # | |
| Show Alignment Source # | |
| Generic Alignment Source # | |
| Arbitrary Alignment Source # | |
| ToJSON Alignment Source # | |
Defined in Text.Pandoc.Definition  | |
| FromJSON Alignment Source # | |
| NFData 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.17.6-EDhd040BTmdH23uw590h1F" 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.
Constructors
| DefaultStyle | |
| Example | |
| Decimal | |
| LowerRoman | |
| UpperRoman | |
| LowerAlpha | |
| UpperAlpha | 
Instances
data ListNumberDelim Source #
Delimiter of list numbers.
Constructors
| DefaultDelim | |
| Period | |
| OneParen | |
| TwoParens | 
Instances
Formats for raw blocks
Instances
| Eq Format Source # | |
| Data Format Source # | |
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 # | |
| Read Format Source # | |
| Show Format Source # | |
| IsString Format Source # | |
Defined in Text.Pandoc.Definition Methods fromString :: String -> Format #  | |
| Generic Format Source # | |
| ToJSON Format Source # | |
Defined in Text.Pandoc.Definition  | |
| FromJSON Format Source # | |
| NFData Format Source # | |
Defined in Text.Pandoc.Definition  | |
| ToJSONFilter a => ToJSONFilter (Maybe Format -> a) Source # | |
Defined in Text.Pandoc.JSON  | |
| type Rep Format Source # | |
Defined in Text.Pandoc.Definition  | |
type Attr = (String, [String], [(String, String)]) Source #
Attributes: identifier, classes, key-value pairs
Type of quotation marks to use in Quoted inline.
Constructors
| SingleQuote | |
| DoubleQuote | 
Instances
| Eq QuoteType Source # | |
| Data QuoteType Source # | |
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 # | |
| Read QuoteType Source # | |
| Show QuoteType Source # | |
| Generic QuoteType Source # | |
| Arbitrary QuoteType Source # | |
| ToJSON QuoteType Source # | |
Defined in Text.Pandoc.Definition  | |
| FromJSON QuoteType Source # | |
| NFData QuoteType Source # | |
Defined in Text.Pandoc.Definition  | |
| type Rep QuoteType Source # | |
Type of math element (display or inline).
Constructors
| DisplayMath | |
| InlineMath | 
Instances
| Eq MathType Source # | |
| Data MathType Source # | |
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 # | |
Defined in Text.Pandoc.Definition  | |
| Read MathType Source # | |
| Show MathType Source # | |
| Generic MathType Source # | |
| Arbitrary MathType Source # | |
| ToJSON MathType Source # | |
Defined in Text.Pandoc.Definition  | |
| FromJSON MathType Source # | |
| NFData MathType Source # | |
Defined in Text.Pandoc.Definition  | |
| type Rep MathType Source # | |
Constructors
| Citation | |
Fields 
  | |
Instances
data CitationMode Source #
Constructors
| AuthorInText | |
| SuppressAuthor | |
| NormalCitation |