{-# LANGUAGE CPP, DeriveDataTypeable #-} #ifdef GENERICS {-# LANGUAGE DeriveGeneric #-} #endif {- Copyright (C) 2006-2010 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Text.Pandoc.Definition Copyright : Copyright (C) 2006-2010 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane Stability : alpha Portability : portable Definition of 'Pandoc' data structure for format-neutral representation of documents. -} module Text.Pandoc.Definition where import Data.Generics (Data, Typeable) import Data.Ord (comparing) #ifdef GENERICS import GHC.Generics (Generic) #define GENERIC , Generic #else #define GENERIC #endif data Pandoc = Pandoc Meta [Block] deriving (Eq, Ord, Read, Show, Typeable, Data GENERIC) -- | Bibliographic information for the document: title, authors, date. data Meta = Meta { docTitle :: [Inline] , docAuthors :: [[Inline]] , docDate :: [Inline] } deriving (Eq, Ord, Show, Read, Typeable, Data GENERIC) -- | Alignment of a table column. data Alignment = AlignLeft | AlignRight | AlignCenter | AlignDefault deriving (Eq, Ord, Show, Read, Typeable, Data GENERIC) -- | List attributes. type ListAttributes = (Int, ListNumberStyle, ListNumberDelim) -- | Style of list numbers. data ListNumberStyle = DefaultStyle | Example | Decimal | LowerRoman | UpperRoman | LowerAlpha | UpperAlpha deriving (Eq, Ord, Show, Read, Typeable, Data GENERIC) -- | Delimiter of list numbers. data ListNumberDelim = DefaultDelim | Period | OneParen | TwoParens deriving (Eq, Ord, Show, Read, Typeable, Data GENERIC) -- | Attributes: identifier, classes, key-value pairs type Attr = (String, [String], [(String, String)]) nullAttr :: Attr nullAttr = ("",[],[]) -- | Table cells are list of Blocks type TableCell = [Block] -- | Formats for raw blocks type Format = String -- | Block element. data Block = Plain [Inline] -- ^ Plain text, not a paragraph | Para [Inline] -- ^ Paragraph | 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, -- relative column widths (0 = default), -- column headers (each a list of blocks), and -- rows (each a list of lists of blocks) | Null -- ^ Nothing deriving (Eq, Ord, Read, Show, Typeable, Data GENERIC) -- | Type of quotation marks to use in Quoted inline. data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Ord, Read, Typeable, Data GENERIC) -- | Link target (URL, title). type Target = (String, String) -- | Type of math element (display or inline). data MathType = DisplayMath | InlineMath deriving (Show, Eq, Ord, Read, Typeable, Data GENERIC) -- | Inline elements. data Inline = 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 | LineBreak -- ^ Hard line break | Math MathType String -- ^ TeX math (literal) | RawInline Format String -- ^ Raw inline | Link [Inline] Target -- ^ Hyperlink: text (list of inlines), target | Image [Inline] Target -- ^ Image: alt text (list of inlines), target | Note [Block] -- ^ Footnote or endnote deriving (Show, Eq, Ord, Read, Typeable, Data GENERIC) data Citation = Citation { citationId :: String , citationPrefix :: [Inline] , citationSuffix :: [Inline] , citationMode :: CitationMode , citationNoteNum :: Int , citationHash :: Int } deriving (Show, Eq, Read, Typeable, Data GENERIC) instance Ord Citation where compare = comparing citationHash data CitationMode = AuthorInText | SuppressAuthor | NormalCitation deriving (Show, Eq, Ord, Read, Typeable, Data GENERIC)