{-# LANGUAGE OverloadedStrings, DeriveDataTypeable, DeriveGeneric,
FlexibleContexts, GeneralizedNewtypeDeriving, PatternGuards, CPP,
TemplateHaskell #-}
module Text.Pandoc.Definition ( Pandoc(..)
, Meta(..)
, MetaValue(..)
, nullMeta
, isNullMeta
, lookupMeta
, docTitle
, docAuthors
, docDate
, Block(..)
, Inline(..)
, ListAttributes
, ListNumberStyle(..)
, ListNumberDelim(..)
, Format(..)
, Attr
, nullAttr
, Caption(..)
, ShortCaption
, RowHeadColumns(..)
, Alignment(..)
, ColWidth(..)
, ColSpec
, Row(..)
, TableHead(..)
, TableBody(..)
, TableFoot(..)
, Cell(..)
, RowSpan(..)
, ColSpan(..)
, QuoteType(..)
, Target
, MathType(..)
, Citation(..)
, CitationMode(..)
, pandocTypesVersion
) where
import Data.Generics (Data, Typeable)
import Data.Ord (comparing)
import Data.Aeson hiding (Null)
import Data.Aeson.TH (deriveJSON)
import qualified Data.Aeson.Types as Aeson
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
import GHC.Generics (Generic)
import Data.String
import Control.DeepSeq
import Paths_pandoc_types (version)
import Data.Version (Version, versionBranch)
import Data.Semigroup (Semigroup(..))
data Pandoc = Pandoc Meta [Block]
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
instance Semigroup Pandoc where
(Pandoc m1 bs1) <> (Pandoc m2 bs2) =
Pandoc (m1 <> m2) (bs1 <> bs2)
instance Monoid Pandoc where
mempty = Pandoc mempty mempty
mappend = (<>)
newtype Meta = Meta { unMeta :: M.Map Text MetaValue }
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
instance Semigroup Meta where
(Meta m1) <> (Meta m2) = Meta (M.union m2 m1)
instance Monoid Meta where
mempty = Meta M.empty
mappend = (<>)
data MetaValue = MetaMap (M.Map Text MetaValue)
| MetaList [MetaValue]
| MetaBool Bool
| MetaString Text
| MetaInlines [Inline]
| MetaBlocks [Block]
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
nullMeta :: Meta
nullMeta = Meta M.empty
isNullMeta :: Meta -> Bool
isNullMeta (Meta m) = M.null m
lookupMeta :: Text -> Meta -> Maybe MetaValue
lookupMeta key (Meta m) = M.lookup key m
docTitle :: Meta -> [Inline]
docTitle meta =
case lookupMeta "title" meta of
Just (MetaString s) -> [Str s]
Just (MetaInlines ils) -> ils
Just (MetaBlocks [Plain ils]) -> ils
Just (MetaBlocks [Para ils]) -> ils
_ -> []
docAuthors :: Meta -> [[Inline]]
docAuthors meta =
case lookupMeta "author" meta of
Just (MetaString s) -> [[Str s]]
Just (MetaInlines ils) -> [ils]
Just (MetaList ms) -> [ils | MetaInlines ils <- ms] ++
[ils | MetaBlocks [Plain ils] <- ms] ++
[ils | MetaBlocks [Para ils] <- ms] ++
[[Str x] | MetaString x <- ms]
_ -> []
docDate :: Meta -> [Inline]
docDate meta =
case lookupMeta "date" meta of
Just (MetaString s) -> [Str s]
Just (MetaInlines ils) -> ils
Just (MetaBlocks [Plain ils]) -> ils
Just (MetaBlocks [Para ils]) -> ils
_ -> []
type ListAttributes = (Int, ListNumberStyle, ListNumberDelim)
data ListNumberStyle = DefaultStyle
| Example
| Decimal
| LowerRoman
| UpperRoman
| LowerAlpha
| UpperAlpha deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
data ListNumberDelim = DefaultDelim
| Period
| OneParen
| TwoParens deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
type Attr = (Text, [Text], [(Text, Text)])
nullAttr :: Attr
nullAttr = ("",[],[])
newtype Format = Format Text
deriving (Read, Show, Typeable, Data, Generic, ToJSON, FromJSON)
instance IsString Format where
fromString f = Format $ T.toCaseFold $ T.pack f
instance Eq Format where
Format x == Format y = T.toCaseFold x == T.toCaseFold y
instance Ord Format where
compare (Format x) (Format y) = compare (T.toCaseFold x) (T.toCaseFold y)
newtype RowHeadColumns = RowHeadColumns Int
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic, Num, Enum, ToJSON, FromJSON)
data Alignment = AlignLeft
| AlignRight
| AlignCenter
| AlignDefault deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
data ColWidth = ColWidth Double
| ColWidthDefault deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
type ColSpec = (Alignment, ColWidth)
data Row = Row Attr [Cell]
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
data TableHead = TableHead Attr [Row]
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
data TableBody = TableBody Attr RowHeadColumns [Row] [Row]
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
data TableFoot = TableFoot Attr [Row]
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
type ShortCaption = [Inline]
data Caption = Caption (Maybe ShortCaption) [Block]
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
data Cell = Cell Attr Alignment RowSpan ColSpan [Block]
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
newtype RowSpan = RowSpan Int
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic, Num, Enum, ToJSON, FromJSON)
newtype ColSpan = ColSpan Int
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic, Num, Enum, ToJSON, FromJSON)
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
| Div Attr [Block]
| Null
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Ord, Read, Typeable, Data, Generic)
type Target = (Text, Text)
data MathType = DisplayMath | InlineMath deriving (Show, Eq, Ord, Read, Typeable, Data, Generic)
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]
deriving (Show, Eq, Ord, Read, Typeable, Data, Generic)
data Citation = Citation { citationId :: Text
, 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)
$(let jsonOpts = defaultOptions
{ allNullaryToStringTag = False
, sumEncoding = TaggedObject { tagFieldName = "t", contentsFieldName = "c" }
}
in fmap concat $ traverse (deriveJSON jsonOpts)
[ ''MetaValue
, ''CitationMode
, ''Citation
, ''QuoteType
, ''MathType
, ''ListNumberStyle
, ''ListNumberDelim
, ''Alignment
, ''ColWidth
, ''Row
, ''Caption
, ''TableHead
, ''TableBody
, ''TableFoot
, ''Cell
, ''Inline
, ''Block
])
instance FromJSON Meta where
parseJSON = fmap Meta . parseJSON
instance ToJSON Meta where
toJSON (Meta m) = toJSON m
toEncoding (Meta m) = toEncoding m
instance FromJSON Pandoc where
parseJSON (Object v) = do
mbJVersion <- v .:? "pandoc-api-version" :: Aeson.Parser (Maybe [Int])
case mbJVersion of
Just jVersion | x : y : _ <- jVersion
, x' : y' : _ <- versionBranch pandocTypesVersion
, x == x'
, y == y' -> Pandoc <$> v .: "meta" <*> v .: "blocks"
| otherwise ->
fail $ mconcat [ "Incompatible API versions: "
, "encoded with "
, show jVersion
, " but attempted to decode with "
, show $ versionBranch pandocTypesVersion
, "."
]
_ -> fail "JSON missing pandoc-api-version."
parseJSON _ = mempty
instance ToJSON Pandoc where
toJSON (Pandoc meta blks) =
object [ "pandoc-api-version" .= versionBranch pandocTypesVersion
, "meta" .= meta
, "blocks" .= blks
]
toEncoding (Pandoc meta blks) =
pairs $ mconcat [ "pandoc-api-version" .= versionBranch pandocTypesVersion
, "meta" .= meta
, "blocks" .= blks
]
instance NFData MetaValue
instance NFData Meta
instance NFData Citation
instance NFData Alignment
instance NFData RowSpan
instance NFData ColSpan
instance NFData Cell
instance NFData Row
instance NFData TableHead
instance NFData TableBody
instance NFData TableFoot
instance NFData Caption
instance NFData Inline
instance NFData MathType
instance NFData Format
instance NFData CitationMode
instance NFData QuoteType
instance NFData ListNumberDelim
instance NFData ListNumberStyle
instance NFData ColWidth
instance NFData RowHeadColumns
instance NFData Block
instance NFData Pandoc
pandocTypesVersion :: Version
pandocTypesVersion = version