aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Definition.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Definition.hs')
-rw-r--r--src/Text/Pandoc/Definition.hs34
1 files changed, 24 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Definition.hs b/src/Text/Pandoc/Definition.hs
index 08ff3905e..b2655ffa0 100644
--- a/src/Text/Pandoc/Definition.hs
+++ b/src/Text/Pandoc/Definition.hs
@@ -1,5 +1,15 @@
--- | Definition of 'Pandoc' data structure for format-neutral representation
--- of documents.
+{- |
+ Module : Text.Pandoc.Definition
+ Copyright : Copyright (C) 2006 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <jgm at berkeley dot edu>
+ Stability : unstable
+ Portability : portable
+
+Definition of 'Pandoc' data structure for format-neutral representation
+of documents.
+-}
module Text.Pandoc.Definition where
data Pandoc = Pandoc Meta [Block] deriving (Eq, Read, Show)
@@ -17,21 +27,24 @@ data Block
| Blank -- ^ A blank line
| Null -- ^ Nothing
| Para [Inline] -- ^ Paragraph
- | Key [Inline] Target -- ^ Reference key: name (list of inlines) and 'Target'
+ | Key [Inline] Target -- ^ Reference key: name (inlines) and 'Target'
| CodeBlock String -- ^ Code block (literal)
| RawHtml String -- ^ Raw HTML block (literal)
| BlockQuote [Block] -- ^ Block quote (list of blocks)
- | OrderedList [[Block]] -- ^ Ordered list (list of items, each a list of blocks)
- | BulletList [[Block]] -- ^ Bullet list (list of items, each a list of blocks)
- | Header Int [Inline] -- ^ Header - level (integer) and text (list of inlines)
+ | OrderedList [[Block]] -- ^ Ordered list (list of items, each
+ -- a list of blocks)
+ | BulletList [[Block]] -- ^ Bullet list (list of items, each
+ -- a list of blocks)
+ | Header Int [Inline] -- ^ Header - level (integer) and text (inlines)
| HorizontalRule -- ^ Horizontal rule
- | Note String [Block] -- ^ Footnote or endnote - reference (string), text (list of blocks)
+ | Note String [Block] -- ^ Footnote or endnote - reference (string),
+ -- text (list of blocks)
deriving (Eq, Read, Show)
-- | Target for a link: either a URL or an indirect (labeled) reference.
data Target
= Src String String -- ^ First string is URL, second is title
- | Ref [Inline] -- ^ Label (list of inlines) for an indirect reference
+ | Ref [Inline] -- ^ Label (list of inlines) for an indirect ref
deriving (Show, Eq, Read)
-- | Inline elements.
@@ -42,9 +55,10 @@ data Inline
| Code String -- ^ Inline code (literal)
| Space -- ^ Inter-word space
| LineBreak -- ^ Hard line break
- | TeX String -- ^ LaTeX code (literal)
+ | TeX String -- ^ LaTeX code (literal)
| HtmlInline String -- ^ HTML code (literal)
| Link [Inline] Target -- ^ Hyperlink: text (list of inlines) and target
- | Image [Inline] Target -- ^ Image: alternative text (list of inlines) and target
+ | Image [Inline] Target -- ^ Image: alternative text (list of inlines)
+ -- and target
| NoteRef String -- ^ Footnote or endnote reference
deriving (Show, Eq, Read)