(original) (raw)

{-# LANGUAGE OverloadedStrings, DeriveDataTypeable, DeriveGeneric, FlexibleContexts, GeneralizedNewtypeDeriving, PatternGuards, CPP, TemplateHaskell , PatternSynonyms, ViewPatterns, StrictData #-}

module Text.Pandoc.Definition ( Pandoc(..) , Meta(..) , MetaValue(..) , nullMeta , isNullMeta , lookupMeta , docTitle , docAuthors , docDate , Block(..) , pattern SimpleFigure , 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 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(..)) import Control.Arrow (second)

data Pandoc = Pandoc Meta [Block] deriving (Pandoc -> Pandoc -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Pandoc -> Pandoc -> Bool $c/= :: Pandoc -> Pandoc -> Bool == :: Pandoc -> Pandoc -> Bool $c== :: Pandoc -> Pandoc -> Bool Eq, Eq Pandoc Pandoc -> Pandoc -> Bool Pandoc -> Pandoc -> Ordering Pandoc -> Pandoc -> Pandoc forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Pandoc -> Pandoc -> Pandoc $cmin :: Pandoc -> Pandoc -> Pandoc max :: Pandoc -> Pandoc -> Pandoc $cmax :: Pandoc -> Pandoc -> Pandoc

= :: Pandoc -> Pandoc -> Bool $c>= :: Pandoc -> Pandoc -> Bool :: Pandoc -> Pandoc -> Bool $c> :: Pandoc -> Pandoc -> Bool <= :: Pandoc -> Pandoc -> Bool $c<= :: Pandoc -> Pandoc -> Bool < :: Pandoc -> Pandoc -> Bool $c< :: Pandoc -> Pandoc -> Bool compare :: Pandoc -> Pandoc -> Ordering $ccompare :: Pandoc -> Pandoc -> Ordering Ord, ReadPrec [Pandoc] ReadPrec Pandoc Int -> ReadS Pandoc ReadS [Pandoc] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Pandoc] $creadListPrec :: ReadPrec [Pandoc] readPrec :: ReadPrec Pandoc $creadPrec :: ReadPrec Pandoc readList :: ReadS [Pandoc] $creadList :: ReadS [Pandoc] readsPrec :: Int -> ReadS Pandoc $creadsPrec :: Int -> ReadS Pandoc Read, Int -> Pandoc -> ShowS [Pandoc] -> ShowS Pandoc -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Pandoc] -> ShowS $cshowList :: [Pandoc] -> ShowS show :: Pandoc -> String $cshow :: Pandoc -> String showsPrec :: Int -> Pandoc -> ShowS $cshowsPrec :: Int -> Pandoc -> ShowS Show, Typeable, Typeable Pandoc Pandoc -> DataType Pandoc -> Constr (forall b. Data b => b -> b) -> Pandoc -> Pandoc forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Pandoc -> u forall u. (forall d. Data d => d -> u) -> Pandoc -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pandoc forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pandoc -> c Pandoc forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pandoc) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pandoc -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pandoc -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Pandoc -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Pandoc -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r gmapT :: (forall b. Data b => b -> b) -> Pandoc -> Pandoc $cgmapT :: (forall b. Data b => b -> b) -> Pandoc -> Pandoc dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pandoc) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pandoc) dataTypeOf :: Pandoc -> DataType $cdataTypeOf :: Pandoc -> DataType toConstr :: Pandoc -> Constr $ctoConstr :: Pandoc -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pandoc $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pandoc gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pandoc -> c Pandoc $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pandoc -> c Pandoc Data, forall x. Rep Pandoc x -> Pandoc forall x. Pandoc -> Rep Pandoc x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Pandoc x -> Pandoc $cfrom :: forall x. Pandoc -> Rep Pandoc x Generic)

instance Semigroup Pandoc where (Pandoc Meta m1 [Block] bs1) <> :: Pandoc -> Pandoc -> Pandoc <> (Pandoc Meta m2 [Block] bs2) = Meta -> [Block] -> Pandoc Pandoc (Meta m1 forall a. Semigroup a => a -> a -> a <> Meta m2) ([Block] bs1 forall a. Semigroup a => a -> a -> a <> [Block] bs2) instance Monoid Pandoc where mempty :: Pandoc mempty = Meta -> [Block] -> Pandoc Pandoc forall a. Monoid a => a mempty forall a. Monoid a => a mempty mappend :: Pandoc -> Pandoc -> Pandoc mappend = forall a. Semigroup a => a -> a -> a (<>)

newtype Meta = Meta { Meta -> Map Text MetaValue unMeta :: M.Map Text MetaValue } deriving (Meta -> Meta -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Meta -> Meta -> Bool $c/= :: Meta -> Meta -> Bool == :: Meta -> Meta -> Bool $c== :: Meta -> Meta -> Bool Eq, Eq Meta Meta -> Meta -> Bool Meta -> Meta -> Ordering Meta -> Meta -> Meta forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Meta -> Meta -> Meta $cmin :: Meta -> Meta -> Meta max :: Meta -> Meta -> Meta $cmax :: Meta -> Meta -> Meta

= :: Meta -> Meta -> Bool $c>= :: Meta -> Meta -> Bool :: Meta -> Meta -> Bool $c> :: Meta -> Meta -> Bool <= :: Meta -> Meta -> Bool $c<= :: Meta -> Meta -> Bool < :: Meta -> Meta -> Bool $c< :: Meta -> Meta -> Bool compare :: Meta -> Meta -> Ordering $ccompare :: Meta -> Meta -> Ordering Ord, Int -> Meta -> ShowS [Meta] -> ShowS Meta -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Meta] -> ShowS $cshowList :: [Meta] -> ShowS show :: Meta -> String $cshow :: Meta -> String showsPrec :: Int -> Meta -> ShowS $cshowsPrec :: Int -> Meta -> ShowS Show, ReadPrec [Meta] ReadPrec Meta Int -> ReadS Meta ReadS [Meta] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Meta] $creadListPrec :: ReadPrec [Meta] readPrec :: ReadPrec Meta $creadPrec :: ReadPrec Meta readList :: ReadS [Meta] $creadList :: ReadS [Meta] readsPrec :: Int -> ReadS Meta $creadsPrec :: Int -> ReadS Meta Read, Typeable, Typeable Meta Meta -> DataType Meta -> Constr (forall b. Data b => b -> b) -> Meta -> Meta forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Meta -> u forall u. (forall d. Data d => d -> u) -> Meta -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Meta -> m Meta forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Meta -> m Meta forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Meta forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Meta -> c Meta forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Meta) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Meta -> m Meta $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Meta -> m Meta gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Meta -> m Meta $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Meta -> m Meta gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Meta -> m Meta $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Meta -> m Meta gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Meta -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Meta -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Meta -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Meta -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r gmapT :: (forall b. Data b => b -> b) -> Meta -> Meta $cgmapT :: (forall b. Data b => b -> b) -> Meta -> Meta dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Meta) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Meta) dataTypeOf :: Meta -> DataType $cdataTypeOf :: Meta -> DataType toConstr :: Meta -> Constr $ctoConstr :: Meta -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Meta $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Meta gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Meta -> c Meta $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Meta -> c Meta Data, forall x. Rep Meta x -> Meta forall x. Meta -> Rep Meta x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Meta x -> Meta $cfrom :: forall x. Meta -> Rep Meta x Generic)

instance Semigroup Meta where (Meta Map Text MetaValue m1) <> :: Meta -> Meta -> Meta <> (Meta Map Text MetaValue m2) = Map Text MetaValue -> Meta Meta (forall k a. Ord k => Map k a -> Map k a -> Map k a M.union Map Text MetaValue m2 Map Text MetaValue m1)

instance Monoid Meta where mempty :: Meta mempty = Map Text MetaValue -> Meta Meta forall k a. Map k a M.empty mappend :: Meta -> Meta -> Meta mappend = forall a. Semigroup a => a -> a -> a (<>)

data MetaValue = MetaMap (M.Map Text MetaValue) | MetaList [MetaValue] | MetaBool Bool | MetaString Text | MetaInlines [Inline] | MetaBlocks [Block] deriving (MetaValue -> MetaValue -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: MetaValue -> MetaValue -> Bool $c/= :: MetaValue -> MetaValue -> Bool == :: MetaValue -> MetaValue -> Bool $c== :: MetaValue -> MetaValue -> Bool Eq, Eq MetaValue MetaValue -> MetaValue -> Bool MetaValue -> MetaValue -> Ordering MetaValue -> MetaValue -> MetaValue forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: MetaValue -> MetaValue -> MetaValue $cmin :: MetaValue -> MetaValue -> MetaValue max :: MetaValue -> MetaValue -> MetaValue $cmax :: MetaValue -> MetaValue -> MetaValue

= :: MetaValue -> MetaValue -> Bool $c>= :: MetaValue -> MetaValue -> Bool :: MetaValue -> MetaValue -> Bool $c> :: MetaValue -> MetaValue -> Bool <= :: MetaValue -> MetaValue -> Bool $c<= :: MetaValue -> MetaValue -> Bool < :: MetaValue -> MetaValue -> Bool $c< :: MetaValue -> MetaValue -> Bool compare :: MetaValue -> MetaValue -> Ordering $ccompare :: MetaValue -> MetaValue -> Ordering Ord, Int -> MetaValue -> ShowS [MetaValue] -> ShowS MetaValue -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [MetaValue] -> ShowS $cshowList :: [MetaValue] -> ShowS show :: MetaValue -> String $cshow :: MetaValue -> String showsPrec :: Int -> MetaValue -> ShowS $cshowsPrec :: Int -> MetaValue -> ShowS Show, ReadPrec [MetaValue] ReadPrec MetaValue Int -> ReadS MetaValue ReadS [MetaValue] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [MetaValue] $creadListPrec :: ReadPrec [MetaValue] readPrec :: ReadPrec MetaValue $creadPrec :: ReadPrec MetaValue readList :: ReadS [MetaValue] $creadList :: ReadS [MetaValue] readsPrec :: Int -> ReadS MetaValue $creadsPrec :: Int -> ReadS MetaValue Read, Typeable, Typeable MetaValue MetaValue -> DataType MetaValue -> Constr (forall b. Data b => b -> b) -> MetaValue -> MetaValue forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> MetaValue -> u forall u. (forall d. Data d => d -> u) -> MetaValue -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetaValue forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetaValue -> c MetaValue forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetaValue) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MetaValue -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MetaValue -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> MetaValue -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> MetaValue -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r gmapT :: (forall b. Data b => b -> b) -> MetaValue -> MetaValue $cgmapT :: (forall b. Data b => b -> b) -> MetaValue -> MetaValue dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetaValue) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetaValue) dataTypeOf :: MetaValue -> DataType $cdataTypeOf :: MetaValue -> DataType toConstr :: MetaValue -> Constr $ctoConstr :: MetaValue -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetaValue $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetaValue gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetaValue -> c MetaValue $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetaValue -> c MetaValue Data, forall x. Rep MetaValue x -> MetaValue forall x. MetaValue -> Rep MetaValue x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep MetaValue x -> MetaValue $cfrom :: forall x. MetaValue -> Rep MetaValue x Generic)

nullMeta :: Meta nullMeta :: Meta nullMeta = Map Text MetaValue -> Meta Meta forall k a. Map k a M.empty

isNullMeta :: Meta -> Bool isNullMeta :: Meta -> Bool isNullMeta (Meta Map Text MetaValue m) = forall k a. Map k a -> Bool M.null Map Text MetaValue m

lookupMeta :: Text -> Meta -> Maybe MetaValue lookupMeta :: Text -> Meta -> Maybe MetaValue lookupMeta Text key (Meta Map Text MetaValue m) = forall k a. Ord k => k -> Map k a -> Maybe a M.lookup Text key Map Text MetaValue m

docTitle :: Meta -> [Inline] docTitle :: Meta -> [Inline] docTitle Meta meta = case Text -> Meta -> Maybe MetaValue lookupMeta Text "title" Meta meta of Just (MetaString Text s) -> [Text -> Inline Str Text s] Just (MetaInlines [Inline] ils) -> [Inline] ils Just (MetaBlocks [Plain [Inline] ils]) -> [Inline] ils Just (MetaBlocks [Para [Inline] ils]) -> [Inline] ils Maybe MetaValue _ -> []

docAuthors :: Meta -> [[Inline]] Meta meta = case Text -> Meta -> Maybe MetaValue lookupMeta Text "author" Meta meta of Just (MetaString Text s) -> [[Text -> Inline Str Text s]] Just (MetaInlines [Inline] ils) -> [[Inline] ils] Just (MetaList [MetaValue] ms) -> [[Inline] ils | MetaInlines [Inline] ils <- [MetaValue] ms] forall a. [a] -> [a] -> [a] ++ [[Inline] ils | MetaBlocks [Plain [Inline] ils] <- [MetaValue] ms] forall a. [a] -> [a] -> [a] ++ [[Inline] ils | MetaBlocks [Para [Inline] ils] <- [MetaValue] ms] forall a. [a] -> [a] -> [a] ++ [[Text -> Inline Str Text x] | MetaString Text x <- [MetaValue] ms] Maybe MetaValue _ -> []

docDate :: Meta -> [Inline] docDate :: Meta -> [Inline] docDate Meta meta = case Text -> Meta -> Maybe MetaValue lookupMeta Text "date" Meta meta of Just (MetaString Text s) -> [Text -> Inline Str Text s] Just (MetaInlines [Inline] ils) -> [Inline] ils Just (MetaBlocks [Plain [Inline] ils]) -> [Inline] ils Just (MetaBlocks [Para [Inline] ils]) -> [Inline] ils Maybe MetaValue _ -> []

type ListAttributes = (Int, ListNumberStyle, ListNumberDelim)

data ListNumberStyle = DefaultStyle | Example | Decimal | LowerRoman | UpperRoman | LowerAlpha | UpperAlpha deriving (ListNumberStyle -> ListNumberStyle -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ListNumberStyle -> ListNumberStyle -> Bool $c/= :: ListNumberStyle -> ListNumberStyle -> Bool == :: ListNumberStyle -> ListNumberStyle -> Bool $c== :: ListNumberStyle -> ListNumberStyle -> Bool Eq, Eq ListNumberStyle ListNumberStyle -> ListNumberStyle -> Bool ListNumberStyle -> ListNumberStyle -> Ordering ListNumberStyle -> ListNumberStyle -> ListNumberStyle forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle $cmin :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle max :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle $cmax :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle

= :: ListNumberStyle -> ListNumberStyle -> Bool $c>= :: ListNumberStyle -> ListNumberStyle -> Bool :: ListNumberStyle -> ListNumberStyle -> Bool $c> :: ListNumberStyle -> ListNumberStyle -> Bool <= :: ListNumberStyle -> ListNumberStyle -> Bool $c<= :: ListNumberStyle -> ListNumberStyle -> Bool < :: ListNumberStyle -> ListNumberStyle -> Bool $c< :: ListNumberStyle -> ListNumberStyle -> Bool compare :: ListNumberStyle -> ListNumberStyle -> Ordering $ccompare :: ListNumberStyle -> ListNumberStyle -> Ordering Ord, Int -> ListNumberStyle -> ShowS [ListNumberStyle] -> ShowS ListNumberStyle -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ListNumberStyle] -> ShowS $cshowList :: [ListNumberStyle] -> ShowS show :: ListNumberStyle -> String $cshow :: ListNumberStyle -> String showsPrec :: Int -> ListNumberStyle -> ShowS $cshowsPrec :: Int -> ListNumberStyle -> ShowS Show, ReadPrec [ListNumberStyle] ReadPrec ListNumberStyle Int -> ReadS ListNumberStyle ReadS [ListNumberStyle] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [ListNumberStyle] $creadListPrec :: ReadPrec [ListNumberStyle] readPrec :: ReadPrec ListNumberStyle $creadPrec :: ReadPrec ListNumberStyle readList :: ReadS [ListNumberStyle] $creadList :: ReadS [ListNumberStyle] readsPrec :: Int -> ReadS ListNumberStyle $creadsPrec :: Int -> ReadS ListNumberStyle Read, Typeable, Typeable ListNumberStyle ListNumberStyle -> DataType ListNumberStyle -> Constr (forall b. Data b => b -> b) -> ListNumberStyle -> ListNumberStyle forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> ListNumberStyle -> u forall u. (forall d. Data d => d -> u) -> ListNumberStyle -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListNumberStyle forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListNumberStyle -> c ListNumberStyle forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListNumberStyle) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListNumberStyle) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ListNumberStyle -> m ListNumberStyle gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListNumberStyle -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListNumberStyle -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberStyle -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberStyle -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r gmapT :: (forall b. Data b => b -> b) -> ListNumberStyle -> ListNumberStyle $cgmapT :: (forall b. Data b => b -> b) -> ListNumberStyle -> ListNumberStyle dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListNumberStyle) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListNumberStyle) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListNumberStyle) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListNumberStyle) dataTypeOf :: ListNumberStyle -> DataType $cdataTypeOf :: ListNumberStyle -> DataType toConstr :: ListNumberStyle -> Constr $ctoConstr :: ListNumberStyle -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListNumberStyle $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListNumberStyle gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListNumberStyle -> c ListNumberStyle $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListNumberStyle -> c ListNumberStyle Data, forall x. Rep ListNumberStyle x -> ListNumberStyle forall x. ListNumberStyle -> Rep ListNumberStyle x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ListNumberStyle x -> ListNumberStyle $cfrom :: forall x. ListNumberStyle -> Rep ListNumberStyle x Generic)

data ListNumberDelim = DefaultDelim | Period | OneParen | TwoParens deriving (ListNumberDelim -> ListNumberDelim -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ListNumberDelim -> ListNumberDelim -> Bool $c/= :: ListNumberDelim -> ListNumberDelim -> Bool == :: ListNumberDelim -> ListNumberDelim -> Bool $c== :: ListNumberDelim -> ListNumberDelim -> Bool Eq, Eq ListNumberDelim ListNumberDelim -> ListNumberDelim -> Bool ListNumberDelim -> ListNumberDelim -> Ordering ListNumberDelim -> ListNumberDelim -> ListNumberDelim forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim $cmin :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim max :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim $cmax :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim

= :: ListNumberDelim -> ListNumberDelim -> Bool $c>= :: ListNumberDelim -> ListNumberDelim -> Bool :: ListNumberDelim -> ListNumberDelim -> Bool $c> :: ListNumberDelim -> ListNumberDelim -> Bool <= :: ListNumberDelim -> ListNumberDelim -> Bool $c<= :: ListNumberDelim -> ListNumberDelim -> Bool < :: ListNumberDelim -> ListNumberDelim -> Bool $c< :: ListNumberDelim -> ListNumberDelim -> Bool compare :: ListNumberDelim -> ListNumberDelim -> Ordering $ccompare :: ListNumberDelim -> ListNumberDelim -> Ordering Ord, Int -> ListNumberDelim -> ShowS [ListNumberDelim] -> ShowS ListNumberDelim -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ListNumberDelim] -> ShowS $cshowList :: [ListNumberDelim] -> ShowS show :: ListNumberDelim -> String $cshow :: ListNumberDelim -> String showsPrec :: Int -> ListNumberDelim -> ShowS $cshowsPrec :: Int -> ListNumberDelim -> ShowS Show, ReadPrec [ListNumberDelim] ReadPrec ListNumberDelim Int -> ReadS ListNumberDelim ReadS [ListNumberDelim] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [ListNumberDelim] $creadListPrec :: ReadPrec [ListNumberDelim] readPrec :: ReadPrec ListNumberDelim $creadPrec :: ReadPrec ListNumberDelim readList :: ReadS [ListNumberDelim] $creadList :: ReadS [ListNumberDelim] readsPrec :: Int -> ReadS ListNumberDelim $creadsPrec :: Int -> ReadS ListNumberDelim Read, Typeable, Typeable ListNumberDelim ListNumberDelim -> DataType ListNumberDelim -> Constr (forall b. Data b => b -> b) -> ListNumberDelim -> ListNumberDelim forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> ListNumberDelim -> u forall u. (forall d. Data d => d -> u) -> ListNumberDelim -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListNumberDelim forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListNumberDelim -> c ListNumberDelim forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListNumberDelim) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListNumberDelim) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ListNumberDelim -> m ListNumberDelim gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListNumberDelim -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListNumberDelim -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberDelim -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberDelim -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r gmapT :: (forall b. Data b => b -> b) -> ListNumberDelim -> ListNumberDelim $cgmapT :: (forall b. Data b => b -> b) -> ListNumberDelim -> ListNumberDelim dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListNumberDelim) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListNumberDelim) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListNumberDelim) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListNumberDelim) dataTypeOf :: ListNumberDelim -> DataType $cdataTypeOf :: ListNumberDelim -> DataType toConstr :: ListNumberDelim -> Constr $ctoConstr :: ListNumberDelim -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListNumberDelim $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListNumberDelim gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListNumberDelim -> c ListNumberDelim $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListNumberDelim -> c ListNumberDelim Data, forall x. Rep ListNumberDelim x -> ListNumberDelim forall x. ListNumberDelim -> Rep ListNumberDelim x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ListNumberDelim x -> ListNumberDelim $cfrom :: forall x. ListNumberDelim -> Rep ListNumberDelim x Generic)

type Attr = (Text, [Text], [(Text, Text)])

nullAttr :: Attr nullAttr :: Attr nullAttr = (Text "",[],[])

newtype Format = Format Text deriving (ReadPrec [Format] ReadPrec Format Int -> ReadS Format ReadS [Format] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Format] $creadListPrec :: ReadPrec [Format] readPrec :: ReadPrec Format $creadPrec :: ReadPrec Format readList :: ReadS [Format] $creadList :: ReadS [Format] readsPrec :: Int -> ReadS Format $creadsPrec :: Int -> ReadS Format Read, Int -> Format -> ShowS [Format] -> ShowS Format -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Format] -> ShowS $cshowList :: [Format] -> ShowS show :: Format -> String $cshow :: Format -> String showsPrec :: Int -> Format -> ShowS $cshowsPrec :: Int -> Format -> ShowS Show, Typeable, Typeable Format Format -> DataType Format -> Constr (forall b. Data b => b -> b) -> Format -> Format forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Format -> u forall u. (forall d. Data d => d -> u) -> Format -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Format -> m Format forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Format forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format -> c Format forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Format) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Format -> m Format $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Format -> m Format gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Format -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Format -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Format -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Format -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r gmapT :: (forall b. Data b => b -> b) -> Format -> Format $cgmapT :: (forall b. Data b => b -> b) -> Format -> Format dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Format) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Format) dataTypeOf :: Format -> DataType $cdataTypeOf :: Format -> DataType toConstr :: Format -> Constr $ctoConstr :: Format -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Format $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Format gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format -> c Format $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format -> c Format Data, forall x. Rep Format x -> Format forall x. Format -> Rep Format x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Format x -> Format $cfrom :: forall x. Format -> Rep Format x Generic, [Format] -> Encoding [Format] -> Value Format -> Encoding Format -> Value forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [Format] -> Encoding $ctoEncodingList :: [Format] -> Encoding toJSONList :: [Format] -> Value $ctoJSONList :: [Format] -> Value toEncoding :: Format -> Encoding $ctoEncoding :: Format -> Encoding toJSON :: Format -> Value $ctoJSON :: Format -> Value ToJSON, Value -> Parser [Format] Value -> Parser Format forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [Format] $cparseJSONList :: Value -> Parser [Format] parseJSON :: Value -> Parser Format $cparseJSON :: Value -> Parser Format FromJSON)

instance IsString Format where fromString :: String -> Format fromString String f = Text -> Format Format forall a b. (a -> b) -> a -> b $ Text -> Text T.toCaseFold forall a b. (a -> b) -> a -> b $ String -> Text T.pack String f

instance Eq Format where Format Text x == :: Format -> Format -> Bool == Format Text y = Text -> Text T.toCaseFold Text x forall a. Eq a => a -> a -> Bool == Text -> Text T.toCaseFold Text y

instance Ord Format where compare :: Format -> Format -> Ordering compare (Format Text x) (Format Text y) = forall a. Ord a => a -> a -> Ordering compare (Text -> Text T.toCaseFold Text x) (Text -> Text T.toCaseFold Text y)

newtype RowHeadColumns = RowHeadColumns Int deriving (RowHeadColumns -> RowHeadColumns -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: RowHeadColumns -> RowHeadColumns -> Bool $c/= :: RowHeadColumns -> RowHeadColumns -> Bool == :: RowHeadColumns -> RowHeadColumns -> Bool $c== :: RowHeadColumns -> RowHeadColumns -> Bool Eq, Eq RowHeadColumns RowHeadColumns -> RowHeadColumns -> Bool RowHeadColumns -> RowHeadColumns -> Ordering RowHeadColumns -> RowHeadColumns -> RowHeadColumns forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns $cmin :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns max :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns $cmax :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns

= :: RowHeadColumns -> RowHeadColumns -> Bool $c>= :: RowHeadColumns -> RowHeadColumns -> Bool :: RowHeadColumns -> RowHeadColumns -> Bool $c> :: RowHeadColumns -> RowHeadColumns -> Bool <= :: RowHeadColumns -> RowHeadColumns -> Bool $c<= :: RowHeadColumns -> RowHeadColumns -> Bool < :: RowHeadColumns -> RowHeadColumns -> Bool $c< :: RowHeadColumns -> RowHeadColumns -> Bool compare :: RowHeadColumns -> RowHeadColumns -> Ordering $ccompare :: RowHeadColumns -> RowHeadColumns -> Ordering Ord, Int -> RowHeadColumns -> ShowS [RowHeadColumns] -> ShowS RowHeadColumns -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [RowHeadColumns] -> ShowS $cshowList :: [RowHeadColumns] -> ShowS show :: RowHeadColumns -> String $cshow :: RowHeadColumns -> String showsPrec :: Int -> RowHeadColumns -> ShowS $cshowsPrec :: Int -> RowHeadColumns -> ShowS Show, ReadPrec [RowHeadColumns] ReadPrec RowHeadColumns Int -> ReadS RowHeadColumns ReadS [RowHeadColumns] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [RowHeadColumns] $creadListPrec :: ReadPrec [RowHeadColumns] readPrec :: ReadPrec RowHeadColumns $creadPrec :: ReadPrec RowHeadColumns readList :: ReadS [RowHeadColumns] $creadList :: ReadS [RowHeadColumns] readsPrec :: Int -> ReadS RowHeadColumns $creadsPrec :: Int -> ReadS RowHeadColumns Read, Typeable, Typeable RowHeadColumns RowHeadColumns -> DataType RowHeadColumns -> Constr (forall b. Data b => b -> b) -> RowHeadColumns -> RowHeadColumns forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> RowHeadColumns -> u forall u. (forall d. Data d => d -> u) -> RowHeadColumns -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowHeadColumns forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowHeadColumns -> c RowHeadColumns forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowHeadColumns) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowHeadColumns) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RowHeadColumns -> m RowHeadColumns gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowHeadColumns -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowHeadColumns -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> RowHeadColumns -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> RowHeadColumns -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r gmapT :: (forall b. Data b => b -> b) -> RowHeadColumns -> RowHeadColumns $cgmapT :: (forall b. Data b => b -> b) -> RowHeadColumns -> RowHeadColumns dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowHeadColumns) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowHeadColumns) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowHeadColumns) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowHeadColumns) dataTypeOf :: RowHeadColumns -> DataType $cdataTypeOf :: RowHeadColumns -> DataType toConstr :: RowHeadColumns -> Constr $ctoConstr :: RowHeadColumns -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowHeadColumns $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowHeadColumns gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowHeadColumns -> c RowHeadColumns $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowHeadColumns -> c RowHeadColumns Data, forall x. Rep RowHeadColumns x -> RowHeadColumns forall x. RowHeadColumns -> Rep RowHeadColumns x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep RowHeadColumns x -> RowHeadColumns $cfrom :: forall x. RowHeadColumns -> Rep RowHeadColumns x Generic, Integer -> RowHeadColumns RowHeadColumns -> RowHeadColumns RowHeadColumns -> RowHeadColumns -> RowHeadColumns forall a. (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (Integer -> a) -> Num a fromInteger :: Integer -> RowHeadColumns $cfromInteger :: Integer -> RowHeadColumns signum :: RowHeadColumns -> RowHeadColumns $csignum :: RowHeadColumns -> RowHeadColumns abs :: RowHeadColumns -> RowHeadColumns $cabs :: RowHeadColumns -> RowHeadColumns negate :: RowHeadColumns -> RowHeadColumns $cnegate :: RowHeadColumns -> RowHeadColumns

data Alignment = AlignLeft | AlignRight | AlignCenter | AlignDefault deriving (Alignment -> Alignment -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Alignment -> Alignment -> Bool $c/= :: Alignment -> Alignment -> Bool == :: Alignment -> Alignment -> Bool $c== :: Alignment -> Alignment -> Bool Eq, Eq Alignment Alignment -> Alignment -> Bool Alignment -> Alignment -> Ordering Alignment -> Alignment -> Alignment forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Alignment -> Alignment -> Alignment $cmin :: Alignment -> Alignment -> Alignment max :: Alignment -> Alignment -> Alignment $cmax :: Alignment -> Alignment -> Alignment

= :: Alignment -> Alignment -> Bool $c>= :: Alignment -> Alignment -> Bool :: Alignment -> Alignment -> Bool $c> :: Alignment -> Alignment -> Bool <= :: Alignment -> Alignment -> Bool $c<= :: Alignment -> Alignment -> Bool < :: Alignment -> Alignment -> Bool $c< :: Alignment -> Alignment -> Bool compare :: Alignment -> Alignment -> Ordering $ccompare :: Alignment -> Alignment -> Ordering Ord, Int -> Alignment -> ShowS [Alignment] -> ShowS Alignment -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Alignment] -> ShowS $cshowList :: [Alignment] -> ShowS show :: Alignment -> String $cshow :: Alignment -> String showsPrec :: Int -> Alignment -> ShowS $cshowsPrec :: Int -> Alignment -> ShowS Show, ReadPrec [Alignment] ReadPrec Alignment Int -> ReadS Alignment ReadS [Alignment] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Alignment] $creadListPrec :: ReadPrec [Alignment] readPrec :: ReadPrec Alignment $creadPrec :: ReadPrec Alignment readList :: ReadS [Alignment] $creadList :: ReadS [Alignment] readsPrec :: Int -> ReadS Alignment $creadsPrec :: Int -> ReadS Alignment Read, Typeable, Typeable Alignment Alignment -> DataType Alignment -> Constr (forall b. Data b => b -> b) -> Alignment -> Alignment forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u forall u. (forall d. Data d => d -> u) -> Alignment -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alignment forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alignment -> c Alignment forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Alignment) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Alignment -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Alignment -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r gmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment $cgmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Alignment) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Alignment) dataTypeOf :: Alignment -> DataType $cdataTypeOf :: Alignment -> DataType toConstr :: Alignment -> Constr $ctoConstr :: Alignment -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alignment $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alignment gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alignment -> c Alignment $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alignment -> c Alignment Data, forall x. Rep Alignment x -> Alignment forall x. Alignment -> Rep Alignment x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Alignment x -> Alignment $cfrom :: forall x. Alignment -> Rep Alignment x Generic)

data ColWidth = ColWidth Double | ColWidthDefault deriving (ColWidth -> ColWidth -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ColWidth -> ColWidth -> Bool $c/= :: ColWidth -> ColWidth -> Bool == :: ColWidth -> ColWidth -> Bool $c== :: ColWidth -> ColWidth -> Bool Eq, Eq ColWidth ColWidth -> ColWidth -> Bool ColWidth -> ColWidth -> Ordering ColWidth -> ColWidth -> ColWidth forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ColWidth -> ColWidth -> ColWidth $cmin :: ColWidth -> ColWidth -> ColWidth max :: ColWidth -> ColWidth -> ColWidth $cmax :: ColWidth -> ColWidth -> ColWidth

= :: ColWidth -> ColWidth -> Bool $c>= :: ColWidth -> ColWidth -> Bool :: ColWidth -> ColWidth -> Bool $c> :: ColWidth -> ColWidth -> Bool <= :: ColWidth -> ColWidth -> Bool $c<= :: ColWidth -> ColWidth -> Bool < :: ColWidth -> ColWidth -> Bool $c< :: ColWidth -> ColWidth -> Bool compare :: ColWidth -> ColWidth -> Ordering $ccompare :: ColWidth -> ColWidth -> Ordering Ord, Int -> ColWidth -> ShowS [ColWidth] -> ShowS ColWidth -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ColWidth] -> ShowS $cshowList :: [ColWidth] -> ShowS show :: ColWidth -> String $cshow :: ColWidth -> String showsPrec :: Int -> ColWidth -> ShowS $cshowsPrec :: Int -> ColWidth -> ShowS Show, ReadPrec [ColWidth] ReadPrec ColWidth Int -> ReadS ColWidth ReadS [ColWidth] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [ColWidth] $creadListPrec :: ReadPrec [ColWidth] readPrec :: ReadPrec ColWidth $creadPrec :: ReadPrec ColWidth readList :: ReadS [ColWidth] $creadList :: ReadS [ColWidth] readsPrec :: Int -> ReadS ColWidth $creadsPrec :: Int -> ReadS ColWidth Read, Typeable, Typeable ColWidth ColWidth -> DataType ColWidth -> Constr (forall b. Data b => b -> b) -> ColWidth -> ColWidth forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> ColWidth -> u forall u. (forall d. Data d => d -> u) -> ColWidth -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColWidth forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColWidth -> c ColWidth forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColWidth) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColWidth -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColWidth -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> ColWidth -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> ColWidth -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r gmapT :: (forall b. Data b => b -> b) -> ColWidth -> ColWidth $cgmapT :: (forall b. Data b => b -> b) -> ColWidth -> ColWidth dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColWidth) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColWidth) dataTypeOf :: ColWidth -> DataType $cdataTypeOf :: ColWidth -> DataType toConstr :: ColWidth -> Constr $ctoConstr :: ColWidth -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColWidth $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColWidth gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColWidth -> c ColWidth $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColWidth -> c ColWidth Data, forall x. Rep ColWidth x -> ColWidth forall x. ColWidth -> Rep ColWidth x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ColWidth x -> ColWidth $cfrom :: forall x. ColWidth -> Rep ColWidth x Generic)

type ColSpec = (Alignment, ColWidth)

data Row = Row Attr [Cell] deriving (Row -> Row -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Row -> Row -> Bool $c/= :: Row -> Row -> Bool == :: Row -> Row -> Bool $c== :: Row -> Row -> Bool Eq, Eq Row Row -> Row -> Bool Row -> Row -> Ordering Row -> Row -> Row forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Row -> Row -> Row $cmin :: Row -> Row -> Row max :: Row -> Row -> Row $cmax :: Row -> Row -> Row

= :: Row -> Row -> Bool $c>= :: Row -> Row -> Bool :: Row -> Row -> Bool $c> :: Row -> Row -> Bool <= :: Row -> Row -> Bool $c<= :: Row -> Row -> Bool < :: Row -> Row -> Bool $c< :: Row -> Row -> Bool compare :: Row -> Row -> Ordering $ccompare :: Row -> Row -> Ordering Ord, Int -> Row -> ShowS [Row] -> ShowS Row -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Row] -> ShowS $cshowList :: [Row] -> ShowS show :: Row -> String $cshow :: Row -> String showsPrec :: Int -> Row -> ShowS $cshowsPrec :: Int -> Row -> ShowS Show, ReadPrec [Row] ReadPrec Row Int -> ReadS Row ReadS [Row] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Row] $creadListPrec :: ReadPrec [Row] readPrec :: ReadPrec Row $creadPrec :: ReadPrec Row readList :: ReadS [Row] $creadList :: ReadS [Row] readsPrec :: Int -> ReadS Row $creadsPrec :: Int -> ReadS Row Read, Typeable, Typeable Row Row -> DataType Row -> Constr (forall b. Data b => b -> b) -> Row -> Row forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Row -> u forall u. (forall d. Data d => d -> u) -> Row -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Row -> m Row forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Row forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Row -> c Row forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Row) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Row -> m Row $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Row -> m Row gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Row -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Row -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Row -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Row -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r gmapT :: (forall b. Data b => b -> b) -> Row -> Row $cgmapT :: (forall b. Data b => b -> b) -> Row -> Row dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Row) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Row) dataTypeOf :: Row -> DataType $cdataTypeOf :: Row -> DataType toConstr :: Row -> Constr $ctoConstr :: Row -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Row $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Row gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Row -> c Row $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Row -> c Row Data, forall x. Rep Row x -> Row forall x. Row -> Rep Row x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Row x -> Row $cfrom :: forall x. Row -> Rep Row x Generic)

data TableHead = TableHead Attr [Row] deriving (TableHead -> TableHead -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TableHead -> TableHead -> Bool $c/= :: TableHead -> TableHead -> Bool == :: TableHead -> TableHead -> Bool $c== :: TableHead -> TableHead -> Bool Eq, Eq TableHead TableHead -> TableHead -> Bool TableHead -> TableHead -> Ordering TableHead -> TableHead -> TableHead forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: TableHead -> TableHead -> TableHead $cmin :: TableHead -> TableHead -> TableHead max :: TableHead -> TableHead -> TableHead $cmax :: TableHead -> TableHead -> TableHead

= :: TableHead -> TableHead -> Bool $c>= :: TableHead -> TableHead -> Bool :: TableHead -> TableHead -> Bool $c> :: TableHead -> TableHead -> Bool <= :: TableHead -> TableHead -> Bool $c<= :: TableHead -> TableHead -> Bool < :: TableHead -> TableHead -> Bool $c< :: TableHead -> TableHead -> Bool compare :: TableHead -> TableHead -> Ordering $ccompare :: TableHead -> TableHead -> Ordering Ord, Int -> TableHead -> ShowS [TableHead] -> ShowS TableHead -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TableHead] -> ShowS $cshowList :: [TableHead] -> ShowS show :: TableHead -> String $cshow :: TableHead -> String showsPrec :: Int -> TableHead -> ShowS $cshowsPrec :: Int -> TableHead -> ShowS Show, ReadPrec [TableHead] ReadPrec TableHead Int -> ReadS TableHead ReadS [TableHead] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [TableHead] $creadListPrec :: ReadPrec [TableHead] readPrec :: ReadPrec TableHead $creadPrec :: ReadPrec TableHead readList :: ReadS [TableHead] $creadList :: ReadS [TableHead] readsPrec :: Int -> ReadS TableHead $creadsPrec :: Int -> ReadS TableHead Read, Typeable, Typeable TableHead TableHead -> DataType TableHead -> Constr (forall b. Data b => b -> b) -> TableHead -> TableHead forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> TableHead -> u forall u. (forall d. Data d => d -> u) -> TableHead -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableHead forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableHead -> c TableHead forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableHead) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableHead -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableHead -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> TableHead -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableHead -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r gmapT :: (forall b. Data b => b -> b) -> TableHead -> TableHead $cgmapT :: (forall b. Data b => b -> b) -> TableHead -> TableHead dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableHead) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableHead) dataTypeOf :: TableHead -> DataType $cdataTypeOf :: TableHead -> DataType toConstr :: TableHead -> Constr $ctoConstr :: TableHead -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableHead $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableHead gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableHead -> c TableHead $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableHead -> c TableHead Data, forall x. Rep TableHead x -> TableHead forall x. TableHead -> Rep TableHead x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep TableHead x -> TableHead $cfrom :: forall x. TableHead -> Rep TableHead x Generic)

data TableBody = TableBody Attr RowHeadColumns [Row] [Row] deriving (TableBody -> TableBody -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TableBody -> TableBody -> Bool $c/= :: TableBody -> TableBody -> Bool == :: TableBody -> TableBody -> Bool $c== :: TableBody -> TableBody -> Bool Eq, Eq TableBody TableBody -> TableBody -> Bool TableBody -> TableBody -> Ordering TableBody -> TableBody -> TableBody forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: TableBody -> TableBody -> TableBody $cmin :: TableBody -> TableBody -> TableBody max :: TableBody -> TableBody -> TableBody $cmax :: TableBody -> TableBody -> TableBody

= :: TableBody -> TableBody -> Bool $c>= :: TableBody -> TableBody -> Bool :: TableBody -> TableBody -> Bool $c> :: TableBody -> TableBody -> Bool <= :: TableBody -> TableBody -> Bool $c<= :: TableBody -> TableBody -> Bool < :: TableBody -> TableBody -> Bool $c< :: TableBody -> TableBody -> Bool compare :: TableBody -> TableBody -> Ordering $ccompare :: TableBody -> TableBody -> Ordering Ord, Int -> TableBody -> ShowS [TableBody] -> ShowS TableBody -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TableBody] -> ShowS $cshowList :: [TableBody] -> ShowS show :: TableBody -> String $cshow :: TableBody -> String showsPrec :: Int -> TableBody -> ShowS $cshowsPrec :: Int -> TableBody -> ShowS Show, ReadPrec [TableBody] ReadPrec TableBody Int -> ReadS TableBody ReadS [TableBody] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [TableBody] $creadListPrec :: ReadPrec [TableBody] readPrec :: ReadPrec TableBody $creadPrec :: ReadPrec TableBody readList :: ReadS [TableBody] $creadList :: ReadS [TableBody] readsPrec :: Int -> ReadS TableBody $creadsPrec :: Int -> ReadS TableBody Read, Typeable, Typeable TableBody TableBody -> DataType TableBody -> Constr (forall b. Data b => b -> b) -> TableBody -> TableBody forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> TableBody -> u forall u. (forall d. Data d => d -> u) -> TableBody -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableBody forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableBody -> c TableBody forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableBody) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableBody -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableBody -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> TableBody -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableBody -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r gmapT :: (forall b. Data b => b -> b) -> TableBody -> TableBody $cgmapT :: (forall b. Data b => b -> b) -> TableBody -> TableBody dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableBody) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableBody) dataTypeOf :: TableBody -> DataType $cdataTypeOf :: TableBody -> DataType toConstr :: TableBody -> Constr $ctoConstr :: TableBody -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableBody $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableBody gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableBody -> c TableBody $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableBody -> c TableBody Data, forall x. Rep TableBody x -> TableBody forall x. TableBody -> Rep TableBody x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep TableBody x -> TableBody $cfrom :: forall x. TableBody -> Rep TableBody x Generic)

data TableFoot = TableFoot Attr [Row] deriving (TableFoot -> TableFoot -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TableFoot -> TableFoot -> Bool $c/= :: TableFoot -> TableFoot -> Bool == :: TableFoot -> TableFoot -> Bool $c== :: TableFoot -> TableFoot -> Bool Eq, Eq TableFoot TableFoot -> TableFoot -> Bool TableFoot -> TableFoot -> Ordering TableFoot -> TableFoot -> TableFoot forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: TableFoot -> TableFoot -> TableFoot $cmin :: TableFoot -> TableFoot -> TableFoot max :: TableFoot -> TableFoot -> TableFoot $cmax :: TableFoot -> TableFoot -> TableFoot

= :: TableFoot -> TableFoot -> Bool $c>= :: TableFoot -> TableFoot -> Bool :: TableFoot -> TableFoot -> Bool $c> :: TableFoot -> TableFoot -> Bool <= :: TableFoot -> TableFoot -> Bool $c<= :: TableFoot -> TableFoot -> Bool < :: TableFoot -> TableFoot -> Bool $c< :: TableFoot -> TableFoot -> Bool compare :: TableFoot -> TableFoot -> Ordering $ccompare :: TableFoot -> TableFoot -> Ordering Ord, Int -> TableFoot -> ShowS [TableFoot] -> ShowS TableFoot -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TableFoot] -> ShowS $cshowList :: [TableFoot] -> ShowS show :: TableFoot -> String $cshow :: TableFoot -> String showsPrec :: Int -> TableFoot -> ShowS $cshowsPrec :: Int -> TableFoot -> ShowS Show, ReadPrec [TableFoot] ReadPrec TableFoot Int -> ReadS TableFoot ReadS [TableFoot] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [TableFoot] $creadListPrec :: ReadPrec [TableFoot] readPrec :: ReadPrec TableFoot $creadPrec :: ReadPrec TableFoot readList :: ReadS [TableFoot] $creadList :: ReadS [TableFoot] readsPrec :: Int -> ReadS TableFoot $creadsPrec :: Int -> ReadS TableFoot Read, Typeable, Typeable TableFoot TableFoot -> DataType TableFoot -> Constr (forall b. Data b => b -> b) -> TableFoot -> TableFoot forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> TableFoot -> u forall u. (forall d. Data d => d -> u) -> TableFoot -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableFoot forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableFoot -> c TableFoot forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableFoot) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableFoot -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableFoot -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> TableFoot -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableFoot -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r gmapT :: (forall b. Data b => b -> b) -> TableFoot -> TableFoot $cgmapT :: (forall b. Data b => b -> b) -> TableFoot -> TableFoot dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableFoot) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableFoot) dataTypeOf :: TableFoot -> DataType $cdataTypeOf :: TableFoot -> DataType toConstr :: TableFoot -> Constr $ctoConstr :: TableFoot -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableFoot $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableFoot gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableFoot -> c TableFoot $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableFoot -> c TableFoot Data, forall x. Rep TableFoot x -> TableFoot forall x. TableFoot -> Rep TableFoot x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep TableFoot x -> TableFoot $cfrom :: forall x. TableFoot -> Rep TableFoot x Generic)

type ShortCaption = [Inline]

data Caption = Caption (Maybe ShortCaption) [Block] deriving (Caption -> Caption -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Caption -> Caption -> Bool $c/= :: Caption -> Caption -> Bool == :: Caption -> Caption -> Bool $c== :: Caption -> Caption -> Bool Eq, Eq Caption Caption -> Caption -> Bool Caption -> Caption -> Ordering Caption -> Caption -> Caption forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Caption -> Caption -> Caption $cmin :: Caption -> Caption -> Caption max :: Caption -> Caption -> Caption $cmax :: Caption -> Caption -> Caption

= :: Caption -> Caption -> Bool $c>= :: Caption -> Caption -> Bool :: Caption -> Caption -> Bool $c> :: Caption -> Caption -> Bool <= :: Caption -> Caption -> Bool $c<= :: Caption -> Caption -> Bool < :: Caption -> Caption -> Bool $c< :: Caption -> Caption -> Bool compare :: Caption -> Caption -> Ordering $ccompare :: Caption -> Caption -> Ordering Ord, Int -> Caption -> ShowS [Caption] -> ShowS Caption -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Caption] -> ShowS $cshowList :: [Caption] -> ShowS show :: Caption -> String $cshow :: Caption -> String showsPrec :: Int -> Caption -> ShowS $cshowsPrec :: Int -> Caption -> ShowS Show, ReadPrec [Caption] ReadPrec Caption Int -> ReadS Caption ReadS [Caption] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Caption] $creadListPrec :: ReadPrec [Caption] readPrec :: ReadPrec Caption $creadPrec :: ReadPrec Caption readList :: ReadS [Caption] $creadList :: ReadS [Caption] readsPrec :: Int -> ReadS Caption $creadsPrec :: Int -> ReadS Caption Read, Typeable, Typeable Caption Caption -> DataType Caption -> Constr (forall b. Data b => b -> b) -> Caption -> Caption forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Caption -> u forall u. (forall d. Data d => d -> u) -> Caption -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Caption -> m Caption forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Caption -> m Caption forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Caption forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Caption -> c Caption forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Caption) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Caption -> m Caption $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Caption -> m Caption gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Caption -> m Caption $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Caption -> m Caption gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Caption -> m Caption $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Caption -> m Caption gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Caption -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Caption -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Caption -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Caption -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r gmapT :: (forall b. Data b => b -> b) -> Caption -> Caption $cgmapT :: (forall b. Data b => b -> b) -> Caption -> Caption dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Caption) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Caption) dataTypeOf :: Caption -> DataType $cdataTypeOf :: Caption -> DataType toConstr :: Caption -> Constr $ctoConstr :: Caption -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Caption $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Caption gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Caption -> c Caption $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Caption -> c Caption Data, forall x. Rep Caption x -> Caption forall x. Caption -> Rep Caption x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Caption x -> Caption $cfrom :: forall x. Caption -> Rep Caption x Generic)

data Cell = Cell Attr Alignment RowSpan ColSpan [Block] deriving (Cell -> Cell -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Cell -> Cell -> Bool $c/= :: Cell -> Cell -> Bool == :: Cell -> Cell -> Bool $c== :: Cell -> Cell -> Bool Eq, Eq Cell Cell -> Cell -> Bool Cell -> Cell -> Ordering Cell -> Cell -> Cell forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Cell -> Cell -> Cell $cmin :: Cell -> Cell -> Cell max :: Cell -> Cell -> Cell $cmax :: Cell -> Cell -> Cell

= :: Cell -> Cell -> Bool $c>= :: Cell -> Cell -> Bool :: Cell -> Cell -> Bool $c> :: Cell -> Cell -> Bool <= :: Cell -> Cell -> Bool $c<= :: Cell -> Cell -> Bool < :: Cell -> Cell -> Bool $c< :: Cell -> Cell -> Bool compare :: Cell -> Cell -> Ordering $ccompare :: Cell -> Cell -> Ordering Ord, Int -> Cell -> ShowS [Cell] -> ShowS Cell -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Cell] -> ShowS $cshowList :: [Cell] -> ShowS show :: Cell -> String $cshow :: Cell -> String showsPrec :: Int -> Cell -> ShowS $cshowsPrec :: Int -> Cell -> ShowS Show, ReadPrec [Cell] ReadPrec Cell Int -> ReadS Cell ReadS [Cell] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Cell] $creadListPrec :: ReadPrec [Cell] readPrec :: ReadPrec Cell $creadPrec :: ReadPrec Cell readList :: ReadS [Cell] $creadList :: ReadS [Cell] readsPrec :: Int -> ReadS Cell $creadsPrec :: Int -> ReadS Cell Read, Typeable, Typeable Cell Cell -> DataType Cell -> Constr (forall b. Data b => b -> b) -> Cell -> Cell forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u forall u. (forall d. Data d => d -> u) -> Cell -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Cell -> m Cell forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cell forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cell -> c Cell forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cell) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Cell -> m Cell $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Cell -> m Cell gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Cell -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Cell -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r gmapT :: (forall b. Data b => b -> b) -> Cell -> Cell $cgmapT :: (forall b. Data b => b -> b) -> Cell -> Cell dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cell) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cell) dataTypeOf :: Cell -> DataType $cdataTypeOf :: Cell -> DataType toConstr :: Cell -> Constr $ctoConstr :: Cell -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cell $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cell gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cell -> c Cell $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cell -> c Cell Data, forall x. Rep Cell x -> Cell forall x. Cell -> Rep Cell x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Cell x -> Cell $cfrom :: forall x. Cell -> Rep Cell x Generic)

newtype RowSpan = RowSpan Int deriving (RowSpan -> RowSpan -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: RowSpan -> RowSpan -> Bool $c/= :: RowSpan -> RowSpan -> Bool == :: RowSpan -> RowSpan -> Bool $c== :: RowSpan -> RowSpan -> Bool Eq, Eq RowSpan RowSpan -> RowSpan -> Bool RowSpan -> RowSpan -> Ordering RowSpan -> RowSpan -> RowSpan forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: RowSpan -> RowSpan -> RowSpan $cmin :: RowSpan -> RowSpan -> RowSpan max :: RowSpan -> RowSpan -> RowSpan $cmax :: RowSpan -> RowSpan -> RowSpan

= :: RowSpan -> RowSpan -> Bool $c>= :: RowSpan -> RowSpan -> Bool :: RowSpan -> RowSpan -> Bool $c> :: RowSpan -> RowSpan -> Bool <= :: RowSpan -> RowSpan -> Bool $c<= :: RowSpan -> RowSpan -> Bool < :: RowSpan -> RowSpan -> Bool $c< :: RowSpan -> RowSpan -> Bool compare :: RowSpan -> RowSpan -> Ordering $ccompare :: RowSpan -> RowSpan -> Ordering Ord, Int -> RowSpan -> ShowS [RowSpan] -> ShowS RowSpan -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [RowSpan] -> ShowS $cshowList :: [RowSpan] -> ShowS show :: RowSpan -> String $cshow :: RowSpan -> String showsPrec :: Int -> RowSpan -> ShowS $cshowsPrec :: Int -> RowSpan -> ShowS Show, ReadPrec [RowSpan] ReadPrec RowSpan Int -> ReadS RowSpan ReadS [RowSpan] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [RowSpan] $creadListPrec :: ReadPrec [RowSpan] readPrec :: ReadPrec RowSpan $creadPrec :: ReadPrec RowSpan readList :: ReadS [RowSpan] $creadList :: ReadS [RowSpan] readsPrec :: Int -> ReadS RowSpan $creadsPrec :: Int -> ReadS RowSpan Read, Typeable, Typeable RowSpan RowSpan -> DataType RowSpan -> Constr (forall b. Data b => b -> b) -> RowSpan -> RowSpan forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> RowSpan -> u forall u. (forall d. Data d => d -> u) -> RowSpan -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowSpan forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowSpan -> c RowSpan forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowSpan) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowSpan -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowSpan -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> RowSpan -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> RowSpan -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r gmapT :: (forall b. Data b => b -> b) -> RowSpan -> RowSpan $cgmapT :: (forall b. Data b => b -> b) -> RowSpan -> RowSpan dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowSpan) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowSpan) dataTypeOf :: RowSpan -> DataType $cdataTypeOf :: RowSpan -> DataType toConstr :: RowSpan -> Constr $ctoConstr :: RowSpan -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowSpan $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowSpan gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowSpan -> c RowSpan $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowSpan -> c RowSpan Data, forall x. Rep RowSpan x -> RowSpan forall x. RowSpan -> Rep RowSpan x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep RowSpan x -> RowSpan $cfrom :: forall x. RowSpan -> Rep RowSpan x Generic, Integer -> RowSpan RowSpan -> RowSpan RowSpan -> RowSpan -> RowSpan forall a. (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (Integer -> a) -> Num a fromInteger :: Integer -> RowSpan $cfromInteger :: Integer -> RowSpan signum :: RowSpan -> RowSpan $csignum :: RowSpan -> RowSpan abs :: RowSpan -> RowSpan $cabs :: RowSpan -> RowSpan negate :: RowSpan -> RowSpan $cnegate :: RowSpan -> RowSpan

newtype ColSpan = ColSpan Int deriving (ColSpan -> ColSpan -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ColSpan -> ColSpan -> Bool $c/= :: ColSpan -> ColSpan -> Bool == :: ColSpan -> ColSpan -> Bool $c== :: ColSpan -> ColSpan -> Bool Eq, Eq ColSpan ColSpan -> ColSpan -> Bool ColSpan -> ColSpan -> Ordering ColSpan -> ColSpan -> ColSpan forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ColSpan -> ColSpan -> ColSpan $cmin :: ColSpan -> ColSpan -> ColSpan max :: ColSpan -> ColSpan -> ColSpan $cmax :: ColSpan -> ColSpan -> ColSpan

= :: ColSpan -> ColSpan -> Bool $c>= :: ColSpan -> ColSpan -> Bool :: ColSpan -> ColSpan -> Bool $c> :: ColSpan -> ColSpan -> Bool <= :: ColSpan -> ColSpan -> Bool $c<= :: ColSpan -> ColSpan -> Bool < :: ColSpan -> ColSpan -> Bool $c< :: ColSpan -> ColSpan -> Bool compare :: ColSpan -> ColSpan -> Ordering $ccompare :: ColSpan -> ColSpan -> Ordering Ord, Int -> ColSpan -> ShowS [ColSpan] -> ShowS ColSpan -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ColSpan] -> ShowS $cshowList :: [ColSpan] -> ShowS show :: ColSpan -> String $cshow :: ColSpan -> String showsPrec :: Int -> ColSpan -> ShowS $cshowsPrec :: Int -> ColSpan -> ShowS Show, ReadPrec [ColSpan] ReadPrec ColSpan Int -> ReadS ColSpan ReadS [ColSpan] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [ColSpan] $creadListPrec :: ReadPrec [ColSpan] readPrec :: ReadPrec ColSpan $creadPrec :: ReadPrec ColSpan readList :: ReadS [ColSpan] $creadList :: ReadS [ColSpan] readsPrec :: Int -> ReadS ColSpan $creadsPrec :: Int -> ReadS ColSpan Read, Typeable, Typeable ColSpan ColSpan -> DataType ColSpan -> Constr (forall b. Data b => b -> b) -> ColSpan -> ColSpan forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> ColSpan -> u forall u. (forall d. Data d => d -> u) -> ColSpan -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColSpan forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColSpan -> c ColSpan forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColSpan) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColSpan -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColSpan -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> ColSpan -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> ColSpan -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r gmapT :: (forall b. Data b => b -> b) -> ColSpan -> ColSpan $cgmapT :: (forall b. Data b => b -> b) -> ColSpan -> ColSpan dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColSpan) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColSpan) dataTypeOf :: ColSpan -> DataType $cdataTypeOf :: ColSpan -> DataType toConstr :: ColSpan -> Constr $ctoConstr :: ColSpan -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColSpan $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColSpan gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColSpan -> c ColSpan $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColSpan -> c ColSpan Data, forall x. Rep ColSpan x -> ColSpan forall x. ColSpan -> Rep ColSpan x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ColSpan x -> ColSpan $cfrom :: forall x. ColSpan -> Rep ColSpan x Generic, Integer -> ColSpan ColSpan -> ColSpan ColSpan -> ColSpan -> ColSpan forall a. (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (Integer -> a) -> Num a fromInteger :: Integer -> ColSpan $cfromInteger :: Integer -> ColSpan signum :: ColSpan -> ColSpan $csignum :: ColSpan -> ColSpan abs :: ColSpan -> ColSpan $cabs :: ColSpan -> ColSpan negate :: ColSpan -> ColSpan $cnegate :: ColSpan -> ColSpan

data Block

= [Plain](Text.Pandoc.Definition.html#Plain) [[Inline](Text.Pandoc.Definition.html#Inline)]

| [Para](Text.Pandoc.Definition.html#Para) [[Inline](Text.Pandoc.Definition.html#Inline)]

| [LineBlock](Text.Pandoc.Definition.html#LineBlock) [[[Inline](Text.Pandoc.Definition.html#Inline)]]

| [CodeBlock](Text.Pandoc.Definition.html#CodeBlock) [Attr](Text.Pandoc.Definition.html#Attr) Text

| [RawBlock](Text.Pandoc.Definition.html#RawBlock) [Format](Text.Pandoc.Definition.html#Format) Text

| [BlockQuote](Text.Pandoc.Definition.html#BlockQuote) [[Block](Text.Pandoc.Definition.html#Block)]


| [OrderedList](Text.Pandoc.Definition.html#OrderedList) [ListAttributes](Text.Pandoc.Definition.html#ListAttributes) [[[Block](Text.Pandoc.Definition.html#Block)]]

| [BulletList](Text.Pandoc.Definition.html#BulletList) [[[Block](Text.Pandoc.Definition.html#Block)]]


| [DefinitionList](Text.Pandoc.Definition.html#DefinitionList) [([[Inline](Text.Pandoc.Definition.html#Inline)],[[[Block](Text.Pandoc.Definition.html#Block)]])]

|  Int [Attr](Text.Pandoc.Definition.html#Attr) [[Inline](Text.Pandoc.Definition.html#Inline)]

| [HorizontalRule](Text.Pandoc.Definition.html#HorizontalRule)


| [Table](Text.Pandoc.Definition.html#Table) [Attr](Text.Pandoc.Definition.html#Attr) [Caption](Text.Pandoc.Definition.html#Caption) [[ColSpec](Text.Pandoc.Definition.html#ColSpec)] [TableHead](Text.Pandoc.Definition.html#TableHead) [[TableBody](Text.Pandoc.Definition.html#TableBody)] [TableFoot](Text.Pandoc.Definition.html#TableFoot)

| [Figure](Text.Pandoc.Definition.html#Figure) [Attr](Text.Pandoc.Definition.html#Attr) [Caption](Text.Pandoc.Definition.html#Caption) [[Block](Text.Pandoc.Definition.html#Block)]

| [Div](Text.Pandoc.Definition.html#Div) [Attr](Text.Pandoc.Definition.html#Attr) [[Block](Text.Pandoc.Definition.html#Block)]
deriving (Block -> Block -> Bool

forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Block -> Block -> Bool $c/= :: Block -> Block -> Bool == :: Block -> Block -> Bool $c== :: Block -> Block -> Bool Eq, Eq Block Block -> Block -> Bool Block -> Block -> Ordering Block -> Block -> Block forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Block -> Block -> Block $cmin :: Block -> Block -> Block max :: Block -> Block -> Block $cmax :: Block -> Block -> Block

= :: Block -> Block -> Bool $c>= :: Block -> Block -> Bool :: Block -> Block -> Bool $c> :: Block -> Block -> Bool <= :: Block -> Block -> Bool $c<= :: Block -> Block -> Bool < :: Block -> Block -> Bool $c< :: Block -> Block -> Bool compare :: Block -> Block -> Ordering $ccompare :: Block -> Block -> Ordering Ord, ReadPrec [Block] ReadPrec Block Int -> ReadS Block ReadS [Block] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Block] $creadListPrec :: ReadPrec [Block] readPrec :: ReadPrec Block $creadPrec :: ReadPrec Block readList :: ReadS [Block] $creadList :: ReadS [Block] readsPrec :: Int -> ReadS Block $creadsPrec :: Int -> ReadS Block Read, Int -> Block -> ShowS [Block] -> ShowS Block -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Block] -> ShowS $cshowList :: [Block] -> ShowS show :: Block -> String $cshow :: Block -> String showsPrec :: Int -> Block -> ShowS $cshowsPrec :: Int -> Block -> ShowS Show, Typeable, Typeable Block Block -> DataType Block -> Constr (forall b. Data b => b -> b) -> Block -> Block forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Block -> u forall u. (forall d. Data d => d -> u) -> Block -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Block -> m Block forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Block -> m Block $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Block -> m Block gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Block -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Block -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Block -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Block -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r gmapT :: (forall b. Data b => b -> b) -> Block -> Block $cgmapT :: (forall b. Data b => b -> b) -> Block -> Block dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) dataTypeOf :: Block -> DataType $cdataTypeOf :: Block -> DataType toConstr :: Block -> Constr $ctoConstr :: Block -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block Data, forall x. Rep Block x -> Block forall x. Block -> Rep Block x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Block x -> Block $cfrom :: forall x. Block -> Rep Block x Generic)

data QuoteType = SingleQuote | DoubleQuote deriving (Int -> QuoteType -> ShowS [QuoteType] -> ShowS QuoteType -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [QuoteType] -> ShowS $cshowList :: [QuoteType] -> ShowS show :: QuoteType -> String $cshow :: QuoteType -> String showsPrec :: Int -> QuoteType -> ShowS $cshowsPrec :: Int -> QuoteType -> ShowS Show, QuoteType -> QuoteType -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: QuoteType -> QuoteType -> Bool $c/= :: QuoteType -> QuoteType -> Bool == :: QuoteType -> QuoteType -> Bool $c== :: QuoteType -> QuoteType -> Bool Eq, Eq QuoteType QuoteType -> QuoteType -> Bool QuoteType -> QuoteType -> Ordering QuoteType -> QuoteType -> QuoteType forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: QuoteType -> QuoteType -> QuoteType $cmin :: QuoteType -> QuoteType -> QuoteType max :: QuoteType -> QuoteType -> QuoteType $cmax :: QuoteType -> QuoteType -> QuoteType

= :: QuoteType -> QuoteType -> Bool $c>= :: QuoteType -> QuoteType -> Bool :: QuoteType -> QuoteType -> Bool $c> :: QuoteType -> QuoteType -> Bool <= :: QuoteType -> QuoteType -> Bool $c<= :: QuoteType -> QuoteType -> Bool < :: QuoteType -> QuoteType -> Bool $c< :: QuoteType -> QuoteType -> Bool compare :: QuoteType -> QuoteType -> Ordering $ccompare :: QuoteType -> QuoteType -> Ordering Ord, ReadPrec [QuoteType] ReadPrec QuoteType Int -> ReadS QuoteType ReadS [QuoteType] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [QuoteType] $creadListPrec :: ReadPrec [QuoteType] readPrec :: ReadPrec QuoteType $creadPrec :: ReadPrec QuoteType readList :: ReadS [QuoteType] $creadList :: ReadS [QuoteType] readsPrec :: Int -> ReadS QuoteType $creadsPrec :: Int -> ReadS QuoteType Read, Typeable, Typeable QuoteType QuoteType -> DataType QuoteType -> Constr (forall b. Data b => b -> b) -> QuoteType -> QuoteType forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> QuoteType -> u forall u. (forall d. Data d => d -> u) -> QuoteType -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteType forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteType -> c QuoteType forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteType) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> QuoteType -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> QuoteType -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> QuoteType -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> QuoteType -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r gmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType $cgmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteType) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteType) dataTypeOf :: QuoteType -> DataType $cdataTypeOf :: QuoteType -> DataType toConstr :: QuoteType -> Constr $ctoConstr :: QuoteType -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteType $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteType gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteType -> c QuoteType $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteType -> c QuoteType Data, forall x. Rep QuoteType x -> QuoteType forall x. QuoteType -> Rep QuoteType x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep QuoteType x -> QuoteType $cfrom :: forall x. QuoteType -> Rep QuoteType x Generic)

type Target = (Text, Text)

isFigureTarget :: Target -> Maybe Target isFigureTarget :: (Text, Text) -> Maybe (Text, Text) isFigureTarget (Text, Text) tgt | (Text src, Just Text tit) <- forall (a :: * -> * -> *) b c d. Arrow a => a b c -> a (d, b) (d, c) second (Text -> Text -> Maybe Text T.stripPrefix Text "fig:") (Text, Text) tgt = forall a. a -> Maybe a Just (Text src, Text tit) | Bool otherwise = forall a. Maybe a Nothing

pattern SimpleFigure :: Attr -> [Inline] -> Target -> Block pattern $bSimpleFigure :: Attr -> [Inline] -> (Text, Text) -> Block $mSimpleFigure :: forall {r}. Block -> (Attr -> [Inline] -> (Text, Text) -> r) -> ((# #) -> r) -> r SimpleFigure attr figureCaption tgt <- Para [Image attr figureCaption (isFigureTarget -> Just tgt)] where SimpleFigure Attr attr [Inline] figureCaption (Text, Text) tgt = [Inline] -> Block Para [Attr -> [Inline] -> (Text, Text) -> Inline Image Attr attr [Inline] figureCaption (forall (a :: * -> * -> *) b c d. Arrow a => a b c -> a (d, b) (d, c) second (Text "fig:" forall a. Semigroup a => a -> a -> a <>) (Text, Text) tgt)]

data MathType = DisplayMath | InlineMath deriving (Int -> MathType -> ShowS [MathType] -> ShowS MathType -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [MathType] -> ShowS $cshowList :: [MathType] -> ShowS show :: MathType -> String $cshow :: MathType -> String showsPrec :: Int -> MathType -> ShowS $cshowsPrec :: Int -> MathType -> ShowS Show, MathType -> MathType -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: MathType -> MathType -> Bool $c/= :: MathType -> MathType -> Bool == :: MathType -> MathType -> Bool $c== :: MathType -> MathType -> Bool Eq, Eq MathType MathType -> MathType -> Bool MathType -> MathType -> Ordering MathType -> MathType -> MathType forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: MathType -> MathType -> MathType $cmin :: MathType -> MathType -> MathType max :: MathType -> MathType -> MathType $cmax :: MathType -> MathType -> MathType

= :: MathType -> MathType -> Bool $c>= :: MathType -> MathType -> Bool :: MathType -> MathType -> Bool $c> :: MathType -> MathType -> Bool <= :: MathType -> MathType -> Bool $c<= :: MathType -> MathType -> Bool < :: MathType -> MathType -> Bool $c< :: MathType -> MathType -> Bool compare :: MathType -> MathType -> Ordering $ccompare :: MathType -> MathType -> Ordering Ord, ReadPrec [MathType] ReadPrec MathType Int -> ReadS MathType ReadS [MathType] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [MathType] $creadListPrec :: ReadPrec [MathType] readPrec :: ReadPrec MathType $creadPrec :: ReadPrec MathType readList :: ReadS [MathType] $creadList :: ReadS [MathType] readsPrec :: Int -> ReadS MathType $creadsPrec :: Int -> ReadS MathType Read, Typeable, Typeable MathType MathType -> DataType MathType -> Constr (forall b. Data b => b -> b) -> MathType -> MathType forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> MathType -> u forall u. (forall d. Data d => d -> u) -> MathType -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> MathType -> m MathType forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MathType forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MathType -> c MathType forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MathType) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> MathType -> m MathType $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> MathType -> m MathType gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MathType -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MathType -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> MathType -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> MathType -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r gmapT :: (forall b. Data b => b -> b) -> MathType -> MathType $cgmapT :: (forall b. Data b => b -> b) -> MathType -> MathType dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MathType) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MathType) dataTypeOf :: MathType -> DataType $cdataTypeOf :: MathType -> DataType toConstr :: MathType -> Constr $ctoConstr :: MathType -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MathType $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MathType gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MathType -> c MathType $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MathType -> c MathType Data, forall x. Rep MathType x -> MathType forall x. MathType -> Rep MathType x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep MathType x -> MathType $cfrom :: forall x. MathType -> Rep MathType x 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 (Int -> Inline -> ShowS [Inline] -> ShowS Inline -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Inline] -> ShowS $cshowList :: [Inline] -> ShowS show :: Inline -> String $cshow :: Inline -> String showsPrec :: Int -> Inline -> ShowS $cshowsPrec :: Int -> Inline -> ShowS Show, Inline -> Inline -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Inline -> Inline -> Bool $c/= :: Inline -> Inline -> Bool == :: Inline -> Inline -> Bool $c== :: Inline -> Inline -> Bool Eq, Eq Inline Inline -> Inline -> Bool Inline -> Inline -> Ordering Inline -> Inline -> Inline forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Inline -> Inline -> Inline $cmin :: Inline -> Inline -> Inline max :: Inline -> Inline -> Inline $cmax :: Inline -> Inline -> Inline

= :: Inline -> Inline -> Bool $c>= :: Inline -> Inline -> Bool :: Inline -> Inline -> Bool $c> :: Inline -> Inline -> Bool <= :: Inline -> Inline -> Bool $c<= :: Inline -> Inline -> Bool < :: Inline -> Inline -> Bool $c< :: Inline -> Inline -> Bool compare :: Inline -> Inline -> Ordering $ccompare :: Inline -> Inline -> Ordering Ord, ReadPrec [Inline] ReadPrec Inline Int -> ReadS Inline ReadS [Inline] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Inline] $creadListPrec :: ReadPrec [Inline] readPrec :: ReadPrec Inline $creadPrec :: ReadPrec Inline readList :: ReadS [Inline] $creadList :: ReadS [Inline] readsPrec :: Int -> ReadS Inline $creadsPrec :: Int -> ReadS Inline Read, Typeable, Typeable Inline Inline -> DataType Inline -> Constr (forall b. Data b => b -> b) -> Inline -> Inline forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Inline -> u forall u. (forall d. Data d => d -> u) -> Inline -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Inline -> m Inline forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inline forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inline -> c Inline forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Inline) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Inline -> m Inline $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Inline -> m Inline gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Inline -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Inline -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Inline -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Inline -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r gmapT :: (forall b. Data b => b -> b) -> Inline -> Inline $cgmapT :: (forall b. Data b => b -> b) -> Inline -> Inline dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Inline) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Inline) dataTypeOf :: Inline -> DataType $cdataTypeOf :: Inline -> DataType toConstr :: Inline -> Constr $ctoConstr :: Inline -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inline $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inline gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inline -> c Inline $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inline -> c Inline Data, forall x. Rep Inline x -> Inline forall x. Inline -> Rep Inline x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Inline x -> Inline $cfrom :: forall x. Inline -> Rep Inline x Generic)

data Citation = Citation { Citation -> Text citationId :: Text , Citation -> [Inline] citationPrefix :: [Inline] , Citation -> [Inline] citationSuffix :: [Inline] , Citation -> CitationMode citationMode :: CitationMode , Citation -> Int citationNoteNum :: Int , Citation -> Int citationHash :: Int } deriving (Int -> Citation -> ShowS [Citation] -> ShowS Citation -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Citation] -> ShowS $cshowList :: [Citation] -> ShowS show :: Citation -> String $cshow :: Citation -> String showsPrec :: Int -> Citation -> ShowS $cshowsPrec :: Int -> Citation -> ShowS Show, Citation -> Citation -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Citation -> Citation -> Bool $c/= :: Citation -> Citation -> Bool == :: Citation -> Citation -> Bool $c== :: Citation -> Citation -> Bool Eq, ReadPrec [Citation] ReadPrec Citation Int -> ReadS Citation ReadS [Citation] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Citation] $creadListPrec :: ReadPrec [Citation] readPrec :: ReadPrec Citation $creadPrec :: ReadPrec Citation readList :: ReadS [Citation] $creadList :: ReadS [Citation] readsPrec :: Int -> ReadS Citation $creadsPrec :: Int -> ReadS Citation Read, Typeable, Typeable Citation Citation -> DataType Citation -> Constr (forall b. Data b => b -> b) -> Citation -> Citation forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Citation -> u forall u. (forall d. Data d => d -> u) -> Citation -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Citation -> m Citation forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Citation forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Citation -> c Citation forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Citation) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Citation -> m Citation $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Citation -> m Citation gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Citation -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Citation -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Citation -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Citation -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r gmapT :: (forall b. Data b => b -> b) -> Citation -> Citation $cgmapT :: (forall b. Data b => b -> b) -> Citation -> Citation dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Citation) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Citation) dataTypeOf :: Citation -> DataType $cdataTypeOf :: Citation -> DataType toConstr :: Citation -> Constr $ctoConstr :: Citation -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Citation $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Citation gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Citation -> c Citation $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Citation -> c Citation Data, forall x. Rep Citation x -> Citation forall x. Citation -> Rep Citation x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Citation x -> Citation $cfrom :: forall x. Citation -> Rep Citation x Generic)

instance Ord Citation where compare :: Citation -> Citation -> Ordering compare = forall a b. Ord a => (b -> a) -> b -> b -> Ordering comparing Citation -> Int citationHash

data CitationMode = AuthorInText | SuppressAuthor | NormalCitation deriving (Int -> CitationMode -> ShowS [CitationMode] -> ShowS CitationMode -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [CitationMode] -> ShowS $cshowList :: [CitationMode] -> ShowS show :: CitationMode -> String $cshow :: CitationMode -> String showsPrec :: Int -> CitationMode -> ShowS $cshowsPrec :: Int -> CitationMode -> ShowS Show, CitationMode -> CitationMode -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CitationMode -> CitationMode -> Bool $c/= :: CitationMode -> CitationMode -> Bool == :: CitationMode -> CitationMode -> Bool $c== :: CitationMode -> CitationMode -> Bool Eq, Eq CitationMode CitationMode -> CitationMode -> Bool CitationMode -> CitationMode -> Ordering CitationMode -> CitationMode -> CitationMode forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: CitationMode -> CitationMode -> CitationMode $cmin :: CitationMode -> CitationMode -> CitationMode max :: CitationMode -> CitationMode -> CitationMode $cmax :: CitationMode -> CitationMode -> CitationMode

= :: CitationMode -> CitationMode -> Bool $c>= :: CitationMode -> CitationMode -> Bool :: CitationMode -> CitationMode -> Bool $c> :: CitationMode -> CitationMode -> Bool <= :: CitationMode -> CitationMode -> Bool $c<= :: CitationMode -> CitationMode -> Bool < :: CitationMode -> CitationMode -> Bool $c< :: CitationMode -> CitationMode -> Bool compare :: CitationMode -> CitationMode -> Ordering $ccompare :: CitationMode -> CitationMode -> Ordering Ord, ReadPrec [CitationMode] ReadPrec CitationMode Int -> ReadS CitationMode ReadS [CitationMode] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [CitationMode] $creadListPrec :: ReadPrec [CitationMode] readPrec :: ReadPrec CitationMode $creadPrec :: ReadPrec CitationMode readList :: ReadS [CitationMode] $creadList :: ReadS [CitationMode] readsPrec :: Int -> ReadS CitationMode $creadsPrec :: Int -> ReadS CitationMode Read, Typeable, Typeable CitationMode CitationMode -> DataType CitationMode -> Constr (forall b. Data b => b -> b) -> CitationMode -> CitationMode forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> CitationMode -> u forall u. (forall d. Data d => d -> u) -> CitationMode -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CitationMode -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CitationMode -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CitationMode forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CitationMode -> c CitationMode forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CitationMode) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CitationMode) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> CitationMode -> m CitationMode gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CitationMode -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CitationMode -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> CitationMode -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> CitationMode -> [u] gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CitationMode -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CitationMode -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CitationMode -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CitationMode -> r gmapT :: (forall b. Data b => b -> b) -> CitationMode -> CitationMode $cgmapT :: (forall b. Data b => b -> b) -> CitationMode -> CitationMode dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CitationMode) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CitationMode) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CitationMode) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CitationMode) dataTypeOf :: CitationMode -> DataType $cdataTypeOf :: CitationMode -> DataType toConstr :: CitationMode -> Constr $ctoConstr :: CitationMode -> Constr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CitationMode $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CitationMode gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CitationMode -> c CitationMode $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CitationMode -> c CitationMode Data, forall x. Rep CitationMode x -> CitationMode forall x. CitationMode -> Rep CitationMode x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep CitationMode x -> CitationMode $cfrom :: forall x. CitationMode -> Rep CitationMode x Generic)

$(let jsonOpts = defaultOptions { allNullaryToStringTag = False , sumEncoding = TaggedObject { tagFieldName = "t", contentsFieldName = "c" } } in 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 :: Value -> Parser Meta parseJSON = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Map Text MetaValue -> Meta Meta forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. FromJSON a => Value -> Parser a parseJSON instance ToJSON Meta where toJSON :: Meta -> Value toJSON (Meta Map Text MetaValue m) = forall a. ToJSON a => a -> Value toJSON Map Text MetaValue m toEncoding :: Meta -> Encoding toEncoding (Meta Map Text MetaValue m) = forall a. ToJSON a => a -> Encoding toEncoding Map Text MetaValue m

instance FromJSON Pandoc where parseJSON :: Value -> Parser Pandoc parseJSON (Object Object v) = do Maybe [Int] mbJVersion <- Object v forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "pandoc-api-version" :: Aeson.Parser (Maybe [Int]) case Maybe [Int] mbJVersion of Just [Int] jVersion | Int x : Int y : [Int] _ <- [Int] jVersion , Int x' : Int y' : [Int] _ <- Version -> [Int] versionBranch Version pandocTypesVersion , Int x forall a. Eq a => a -> a -> Bool == Int x' , Int y forall a. Eq a => a -> a -> Bool == Int y' -> Meta -> [Block] -> Pandoc Pandoc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object v forall a. FromJSON a => Object -> Key -> Parser a .: Key "meta" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object v forall a. FromJSON a => Object -> Key -> Parser a .: Key "blocks" | Bool otherwise -> forall (m :: * -> *) a. MonadFail m => String -> m a fail forall a b. (a -> b) -> a -> b $ forall a. Monoid a => [a] -> a mconcat [ String "Incompatible API versions: " , String "encoded with " , forall a. Show a => a -> String show [Int] jVersion , String " but attempted to decode with " , forall a. Show a => a -> String show forall a b. (a -> b) -> a -> b $ Version -> [Int] versionBranch Version pandocTypesVersion , String "." ] Maybe [Int] _ -> forall (m :: * -> *) a. MonadFail m => String -> m a fail String "JSON missing pandoc-api-version." parseJSON Value _ = forall a. Monoid a => a mempty instance ToJSON Pandoc where toJSON :: Pandoc -> Value toJSON (Pandoc Meta meta [Block] blks) = [Pair] -> Value object [ Key "pandoc-api-version" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Version -> [Int] versionBranch Version pandocTypesVersion , Key "meta" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Meta meta , Key "blocks" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= [Block] blks ] toEncoding :: Pandoc -> Encoding toEncoding (Pandoc Meta meta [Block] blks) = Series -> Encoding pairs forall a b. (a -> b) -> a -> b $ forall a. Monoid a => [a] -> a mconcat [ Key "pandoc-api-version" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Version -> [Int] versionBranch Version pandocTypesVersion , Key "meta" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Meta meta , Key "blocks" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= [Block] 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 pandocTypesVersion = Version version