module Text.Pandoc.Definition ( Pandoc(..)
, Meta(..)
, MetaValue(..)
, nullMeta
, isNullMeta
, lookupMeta
, docTitle
, docAuthors
, docDate
, Block(..)
, Inline(..)
, Alignment(..)
, ListAttributes
, ListNumberStyle(..)
, ListNumberDelim(..)
, Format(..)
, Attr
, nullAttr
, TableCell
, QuoteType(..)
, Target
, MathType(..)
, Citation(..)
, CitationMode(..)
) where
import Data.Generics (Data, Typeable)
import Data.Ord (comparing)
import Data.Aeson (FromJSON(..), ToJSON(..))
import qualified Data.Aeson.Types as Aeson
import Control.Monad (guard)
import qualified Data.Map as M
import GHC.Generics (Generic, Rep (..))
import Data.String
import Data.Char (toLower)
import Data.Monoid
import Control.DeepSeq.Generics
data Pandoc = Pandoc Meta [Block]
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
instance Monoid Pandoc where
mempty = Pandoc mempty mempty
(Pandoc m1 bs1) `mappend` (Pandoc m2 bs2) =
Pandoc (m1 `mappend` m2) (bs1 `mappend` bs2)
newtype Meta = Meta { unMeta :: M.Map String MetaValue }
deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
instance Monoid Meta where
mempty = Meta (M.empty)
(Meta m1) `mappend` (Meta m2) = Meta (M.union m1 m2)
data MetaValue = MetaMap (M.Map String MetaValue)
| MetaList [MetaValue]
| MetaBool Bool
| MetaString String
| 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 :: String -> 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
_ -> []
data Alignment = AlignLeft
| AlignRight
| AlignCenter
| AlignDefault deriving (Eq, Ord, Show, Read, Typeable, Data, Generic)
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 = (String, [String], [(String, String)])
nullAttr :: Attr
nullAttr = ("",[],[])
type TableCell = [Block]
newtype Format = Format String
deriving (Read, Show, Typeable, Data, Generic)
instance IsString Format where
fromString f = Format $ map toLower f
instance Eq Format where
Format x == Format y = map toLower x == map toLower y
instance Ord Format where
compare (Format x) (Format y) = compare (map toLower x) (map toLower y)
data Block
= Plain [Inline]
| Para [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
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Ord, Read, Typeable, Data, Generic)
type Target = (String, String)
data MathType = DisplayMath | InlineMath deriving (Show, Eq, Ord, Read, Typeable, Data, Generic)
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
| LineBreak
| Math MathType String
| RawInline Format String
| Link [Inline] Target
| Image [Inline] Target
| Note [Block]
| Span Attr [Inline]
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)
jsonOpts :: Aeson.Options
jsonOpts = Aeson.defaultOptions{
Aeson.fieldLabelModifier = id
, Aeson.constructorTagModifier = id
, Aeson.allNullaryToStringTag = False
, Aeson.omitNothingFields = False
, Aeson.sumEncoding = Aeson.TaggedObject "t" "c"
}
toJSON' :: (Generic a, Aeson.GToJSON (Rep a))
=> a -> Aeson.Value
toJSON' = Aeson.genericToJSON jsonOpts
parseJSON' :: (Generic a, Aeson.GFromJSON (Rep a))
=> Aeson.Value -> Aeson.Parser a
parseJSON' = Aeson.genericParseJSON jsonOpts
instance FromJSON MetaValue
where parseJSON = parseJSON'
instance ToJSON MetaValue
where toJSON = toJSON'
instance FromJSON Meta
where parseJSON = parseJSON'
instance ToJSON Meta
where toJSON = toJSON'
instance FromJSON CitationMode
where parseJSON = parseJSON'
instance ToJSON CitationMode
where toJSON = toJSON'
instance FromJSON Citation
where parseJSON = parseJSON'
instance ToJSON Citation
where toJSON = toJSON'
instance FromJSON QuoteType
where parseJSON = parseJSON'
instance ToJSON QuoteType
where toJSON = toJSON'
instance FromJSON MathType
where parseJSON = parseJSON'
instance ToJSON MathType
where toJSON = toJSON'
instance FromJSON ListNumberStyle
where parseJSON = parseJSON'
instance ToJSON ListNumberStyle
where toJSON = toJSON'
instance FromJSON ListNumberDelim
where parseJSON = parseJSON'
instance ToJSON ListNumberDelim
where toJSON = toJSON'
instance FromJSON Alignment
where parseJSON = parseJSON'
instance ToJSON Alignment
where toJSON = toJSON'
instance FromJSON Format
where parseJSON = parseJSON'
instance ToJSON Format
where toJSON = toJSON'
instance FromJSON Inline
where parseJSON = parseJSON'
instance ToJSON Inline
where toJSON = toJSON'
instance FromJSON Block
where parseJSON = parseJSON'
instance ToJSON Block
where toJSON = toJSON'
instance FromJSON Pandoc
where parseJSON = parseJSON'
instance ToJSON Pandoc
where toJSON = toJSON'
instance NFData MetaValue where rnf = genericRnf
instance NFData Meta where rnf = genericRnf
instance NFData Citation where rnf = genericRnf
instance NFData Alignment where rnf = genericRnf
instance NFData Inline where rnf = genericRnf
instance NFData MathType where rnf = genericRnf
instance NFData Format where rnf = genericRnf
instance NFData CitationMode where rnf = genericRnf
instance NFData QuoteType where rnf = genericRnf
instance NFData ListNumberDelim where rnf = genericRnf
instance NFData ListNumberStyle where rnf = genericRnf
instance NFData Block where rnf = genericRnf
instance NFData Pandoc where rnf = genericRnf