{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.Pandoc.Options ( module Text.Pandoc.Extensions
, ReaderOptions(..)
, HTMLMathMethod (..)
, CiteMethod (..)
, ObfuscationMethod (..)
, HTMLSlideVariant (..)
, EPUBVersion (..)
, WrapOption (..)
, TopLevelDivision (..)
, WriterOptions (..)
, TrackChanges (..)
, ReferenceLocation (..)
, def
, isEnabled
, defaultMathJaxURL
, defaultKaTeXURL
) where
import Control.Applicative ((<|>))
import Data.Char (toLower)
import Data.Maybe (fromMaybe)
import Data.Data (Data)
import Data.Default
import Data.Text (Text)
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Skylighting (SyntaxMap, defaultSyntaxMap)
import Text.DocTemplates (Context(..), Template)
import Text.Pandoc.Extensions
import Text.Pandoc.Highlighting (Style, pygments)
import Text.Pandoc.Shared (camelCaseStrToHyphenated)
import Data.Aeson.TH (deriveJSON, defaultOptions, Options(..),
SumEncoding(..))
import Data.YAML
class HasSyntaxExtensions a where
getExtensions :: a -> Extensions
data ReaderOptions = ReaderOptions{
ReaderOptions -> Extensions
readerExtensions :: Extensions
, ReaderOptions -> Bool
readerStandalone :: Bool
, ReaderOptions -> Int
readerColumns :: Int
, ReaderOptions -> Int
readerTabStop :: Int
, ReaderOptions -> [Text]
readerIndentedCodeClasses :: [Text]
, ReaderOptions -> Set Text
readerAbbreviations :: Set.Set Text
, ReaderOptions -> Text
readerDefaultImageExtension :: Text
, ReaderOptions -> TrackChanges
readerTrackChanges :: TrackChanges
, :: Bool
} deriving (Int -> ReaderOptions -> ShowS
[ReaderOptions] -> ShowS
ReaderOptions -> String
(Int -> ReaderOptions -> ShowS)
-> (ReaderOptions -> String)
-> ([ReaderOptions] -> ShowS)
-> Show ReaderOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReaderOptions] -> ShowS
$cshowList :: [ReaderOptions] -> ShowS
show :: ReaderOptions -> String
$cshow :: ReaderOptions -> String
showsPrec :: Int -> ReaderOptions -> ShowS
$cshowsPrec :: Int -> ReaderOptions -> ShowS
Show, ReadPrec [ReaderOptions]
ReadPrec ReaderOptions
Int -> ReadS ReaderOptions
ReadS [ReaderOptions]
(Int -> ReadS ReaderOptions)
-> ReadS [ReaderOptions]
-> ReadPrec ReaderOptions
-> ReadPrec [ReaderOptions]
-> Read ReaderOptions
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReaderOptions]
$creadListPrec :: ReadPrec [ReaderOptions]
readPrec :: ReadPrec ReaderOptions
$creadPrec :: ReadPrec ReaderOptions
readList :: ReadS [ReaderOptions]
$creadList :: ReadS [ReaderOptions]
readsPrec :: Int -> ReadS ReaderOptions
$creadsPrec :: Int -> ReadS ReaderOptions
Read, Typeable ReaderOptions
DataType
Constr
Typeable ReaderOptions
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReaderOptions -> c ReaderOptions)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReaderOptions)
-> (ReaderOptions -> Constr)
-> (ReaderOptions -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReaderOptions))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReaderOptions))
-> ((forall b. Data b => b -> b) -> ReaderOptions -> ReaderOptions)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r)
-> (forall u. (forall d. Data d => d -> u) -> ReaderOptions -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ReaderOptions -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions)
-> Data ReaderOptions
ReaderOptions -> DataType
ReaderOptions -> Constr
(forall b. Data b => b -> b) -> ReaderOptions -> ReaderOptions
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReaderOptions -> c ReaderOptions
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReaderOptions
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) -> ReaderOptions -> u
forall u. (forall d. Data d => d -> u) -> ReaderOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReaderOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReaderOptions -> c ReaderOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReaderOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReaderOptions)
$cReaderOptions :: Constr
$tReaderOptions :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
gmapMp :: (forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
gmapM :: (forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
gmapQi :: Int -> (forall d. Data d => d -> u) -> ReaderOptions -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReaderOptions -> u
gmapQ :: (forall d. Data d => d -> u) -> ReaderOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReaderOptions -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
gmapT :: (forall b. Data b => b -> b) -> ReaderOptions -> ReaderOptions
$cgmapT :: (forall b. Data b => b -> b) -> ReaderOptions -> ReaderOptions
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReaderOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReaderOptions)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ReaderOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReaderOptions)
dataTypeOf :: ReaderOptions -> DataType
$cdataTypeOf :: ReaderOptions -> DataType
toConstr :: ReaderOptions -> Constr
$ctoConstr :: ReaderOptions -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReaderOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReaderOptions
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReaderOptions -> c ReaderOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReaderOptions -> c ReaderOptions
$cp1Data :: Typeable ReaderOptions
Data, Typeable, (forall x. ReaderOptions -> Rep ReaderOptions x)
-> (forall x. Rep ReaderOptions x -> ReaderOptions)
-> Generic ReaderOptions
forall x. Rep ReaderOptions x -> ReaderOptions
forall x. ReaderOptions -> Rep ReaderOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReaderOptions x -> ReaderOptions
$cfrom :: forall x. ReaderOptions -> Rep ReaderOptions x
Generic)
instance HasSyntaxExtensions ReaderOptions where
getExtensions :: ReaderOptions -> Extensions
getExtensions ReaderOptions
opts = ReaderOptions -> Extensions
readerExtensions ReaderOptions
opts
instance Default ReaderOptions
where def :: ReaderOptions
def = ReaderOptions :: Extensions
-> Bool
-> Int
-> Int
-> [Text]
-> Set Text
-> Text
-> TrackChanges
-> Bool
-> ReaderOptions
ReaderOptions{
readerExtensions :: Extensions
readerExtensions = Extensions
emptyExtensions
, readerStandalone :: Bool
readerStandalone = Bool
False
, readerColumns :: Int
readerColumns = Int
80
, readerTabStop :: Int
readerTabStop = Int
4
, readerIndentedCodeClasses :: [Text]
readerIndentedCodeClasses = []
, readerAbbreviations :: Set Text
readerAbbreviations = Set Text
defaultAbbrevs
, readerDefaultImageExtension :: Text
readerDefaultImageExtension = Text
""
, readerTrackChanges :: TrackChanges
readerTrackChanges = TrackChanges
AcceptChanges
, readerStripComments :: Bool
readerStripComments = Bool
False
}
defaultAbbrevs :: Set.Set Text
defaultAbbrevs :: Set Text
defaultAbbrevs = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList
[ Text
"Mr.", Text
"Mrs.", Text
"Ms.", Text
"Capt.", Text
"Dr.", Text
"Prof.",
Text
"Gen.", Text
"Gov.", Text
"e.g.", Text
"i.e.", Text
"Sgt.", Text
"St.",
Text
"vol.", Text
"vs.", Text
"Sen.", Text
"Rep.", Text
"Pres.", Text
"Hon.",
Text
"Rev.", Text
"Ph.D.", Text
"M.D.", Text
"M.A.", Text
"p.", Text
"pp.",
Text
"ch.", Text
"sec.", Text
"cf.", Text
"cp."]
data EPUBVersion = EPUB2 | EPUB3 deriving (EPUBVersion -> EPUBVersion -> Bool
(EPUBVersion -> EPUBVersion -> Bool)
-> (EPUBVersion -> EPUBVersion -> Bool) -> Eq EPUBVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EPUBVersion -> EPUBVersion -> Bool
$c/= :: EPUBVersion -> EPUBVersion -> Bool
== :: EPUBVersion -> EPUBVersion -> Bool
$c== :: EPUBVersion -> EPUBVersion -> Bool
Eq, Int -> EPUBVersion -> ShowS
[EPUBVersion] -> ShowS
EPUBVersion -> String
(Int -> EPUBVersion -> ShowS)
-> (EPUBVersion -> String)
-> ([EPUBVersion] -> ShowS)
-> Show EPUBVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EPUBVersion] -> ShowS
$cshowList :: [EPUBVersion] -> ShowS
show :: EPUBVersion -> String
$cshow :: EPUBVersion -> String
showsPrec :: Int -> EPUBVersion -> ShowS
$cshowsPrec :: Int -> EPUBVersion -> ShowS
Show, ReadPrec [EPUBVersion]
ReadPrec EPUBVersion
Int -> ReadS EPUBVersion
ReadS [EPUBVersion]
(Int -> ReadS EPUBVersion)
-> ReadS [EPUBVersion]
-> ReadPrec EPUBVersion
-> ReadPrec [EPUBVersion]
-> Read EPUBVersion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EPUBVersion]
$creadListPrec :: ReadPrec [EPUBVersion]
readPrec :: ReadPrec EPUBVersion
$creadPrec :: ReadPrec EPUBVersion
readList :: ReadS [EPUBVersion]
$creadList :: ReadS [EPUBVersion]
readsPrec :: Int -> ReadS EPUBVersion
$creadsPrec :: Int -> ReadS EPUBVersion
Read, Typeable EPUBVersion
DataType
Constr
Typeable EPUBVersion
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EPUBVersion -> c EPUBVersion)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EPUBVersion)
-> (EPUBVersion -> Constr)
-> (EPUBVersion -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EPUBVersion))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EPUBVersion))
-> ((forall b. Data b => b -> b) -> EPUBVersion -> EPUBVersion)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r)
-> (forall u. (forall d. Data d => d -> u) -> EPUBVersion -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> EPUBVersion -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion)
-> Data EPUBVersion
EPUBVersion -> DataType
EPUBVersion -> Constr
(forall b. Data b => b -> b) -> EPUBVersion -> EPUBVersion
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EPUBVersion -> c EPUBVersion
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EPUBVersion
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) -> EPUBVersion -> u
forall u. (forall d. Data d => d -> u) -> EPUBVersion -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EPUBVersion
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EPUBVersion -> c EPUBVersion
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EPUBVersion)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EPUBVersion)
$cEPUB3 :: Constr
$cEPUB2 :: Constr
$tEPUBVersion :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
gmapMp :: (forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
gmapM :: (forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
gmapQi :: Int -> (forall d. Data d => d -> u) -> EPUBVersion -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> EPUBVersion -> u
gmapQ :: (forall d. Data d => d -> u) -> EPUBVersion -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EPUBVersion -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
gmapT :: (forall b. Data b => b -> b) -> EPUBVersion -> EPUBVersion
$cgmapT :: (forall b. Data b => b -> b) -> EPUBVersion -> EPUBVersion
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EPUBVersion)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EPUBVersion)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c EPUBVersion)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EPUBVersion)
dataTypeOf :: EPUBVersion -> DataType
$cdataTypeOf :: EPUBVersion -> DataType
toConstr :: EPUBVersion -> Constr
$ctoConstr :: EPUBVersion -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EPUBVersion
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EPUBVersion
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EPUBVersion -> c EPUBVersion
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EPUBVersion -> c EPUBVersion
$cp1Data :: Typeable EPUBVersion
Data, Typeable, (forall x. EPUBVersion -> Rep EPUBVersion x)
-> (forall x. Rep EPUBVersion x -> EPUBVersion)
-> Generic EPUBVersion
forall x. Rep EPUBVersion x -> EPUBVersion
forall x. EPUBVersion -> Rep EPUBVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EPUBVersion x -> EPUBVersion
$cfrom :: forall x. EPUBVersion -> Rep EPUBVersion x
Generic)
data HTMLMathMethod = PlainMath
| WebTeX Text
| GladTeX
| MathML
| MathJax Text
| KaTeX Text
deriving (Int -> HTMLMathMethod -> ShowS
[HTMLMathMethod] -> ShowS
HTMLMathMethod -> String
(Int -> HTMLMathMethod -> ShowS)
-> (HTMLMathMethod -> String)
-> ([HTMLMathMethod] -> ShowS)
-> Show HTMLMathMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HTMLMathMethod] -> ShowS
$cshowList :: [HTMLMathMethod] -> ShowS
show :: HTMLMathMethod -> String
$cshow :: HTMLMathMethod -> String
showsPrec :: Int -> HTMLMathMethod -> ShowS
$cshowsPrec :: Int -> HTMLMathMethod -> ShowS
Show, ReadPrec [HTMLMathMethod]
ReadPrec HTMLMathMethod
Int -> ReadS HTMLMathMethod
ReadS [HTMLMathMethod]
(Int -> ReadS HTMLMathMethod)
-> ReadS [HTMLMathMethod]
-> ReadPrec HTMLMathMethod
-> ReadPrec [HTMLMathMethod]
-> Read HTMLMathMethod
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HTMLMathMethod]
$creadListPrec :: ReadPrec [HTMLMathMethod]
readPrec :: ReadPrec HTMLMathMethod
$creadPrec :: ReadPrec HTMLMathMethod
readList :: ReadS [HTMLMathMethod]
$creadList :: ReadS [HTMLMathMethod]
readsPrec :: Int -> ReadS HTMLMathMethod
$creadsPrec :: Int -> ReadS HTMLMathMethod
Read, HTMLMathMethod -> HTMLMathMethod -> Bool
(HTMLMathMethod -> HTMLMathMethod -> Bool)
-> (HTMLMathMethod -> HTMLMathMethod -> Bool) -> Eq HTMLMathMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HTMLMathMethod -> HTMLMathMethod -> Bool
$c/= :: HTMLMathMethod -> HTMLMathMethod -> Bool
== :: HTMLMathMethod -> HTMLMathMethod -> Bool
$c== :: HTMLMathMethod -> HTMLMathMethod -> Bool
Eq, Typeable HTMLMathMethod
DataType
Constr
Typeable HTMLMathMethod
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLMathMethod)
-> (HTMLMathMethod -> Constr)
-> (HTMLMathMethod -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLMathMethod))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLMathMethod))
-> ((forall b. Data b => b -> b)
-> HTMLMathMethod -> HTMLMathMethod)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r)
-> (forall u.
(forall d. Data d => d -> u) -> HTMLMathMethod -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> HTMLMathMethod -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod)
-> Data HTMLMathMethod
HTMLMathMethod -> DataType
HTMLMathMethod -> Constr
(forall b. Data b => b -> b) -> HTMLMathMethod -> HTMLMathMethod
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLMathMethod
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) -> HTMLMathMethod -> u
forall u. (forall d. Data d => d -> u) -> HTMLMathMethod -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLMathMethod
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLMathMethod)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLMathMethod)
$cKaTeX :: Constr
$cMathJax :: Constr
$cMathML :: Constr
$cGladTeX :: Constr
$cWebTeX :: Constr
$cPlainMath :: Constr
$tHTMLMathMethod :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
gmapMp :: (forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
gmapM :: (forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
gmapQi :: Int -> (forall d. Data d => d -> u) -> HTMLMathMethod -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HTMLMathMethod -> u
gmapQ :: (forall d. Data d => d -> u) -> HTMLMathMethod -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HTMLMathMethod -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
gmapT :: (forall b. Data b => b -> b) -> HTMLMathMethod -> HTMLMathMethod
$cgmapT :: (forall b. Data b => b -> b) -> HTMLMathMethod -> HTMLMathMethod
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLMathMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLMathMethod)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c HTMLMathMethod)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLMathMethod)
dataTypeOf :: HTMLMathMethod -> DataType
$cdataTypeOf :: HTMLMathMethod -> DataType
toConstr :: HTMLMathMethod -> Constr
$ctoConstr :: HTMLMathMethod -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLMathMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLMathMethod
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod
$cp1Data :: Typeable HTMLMathMethod
Data, Typeable, (forall x. HTMLMathMethod -> Rep HTMLMathMethod x)
-> (forall x. Rep HTMLMathMethod x -> HTMLMathMethod)
-> Generic HTMLMathMethod
forall x. Rep HTMLMathMethod x -> HTMLMathMethod
forall x. HTMLMathMethod -> Rep HTMLMathMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HTMLMathMethod x -> HTMLMathMethod
$cfrom :: forall x. HTMLMathMethod -> Rep HTMLMathMethod x
Generic)
instance FromYAML HTMLMathMethod where
parseYAML :: Node Pos -> Parser HTMLMathMethod
parseYAML Node Pos
node =
(String
-> (Mapping Pos -> Parser HTMLMathMethod)
-> Node Pos
-> Parser HTMLMathMethod
forall a.
String -> (Mapping Pos -> Parser a) -> Node Pos -> Parser a
withMap String
"HTMLMathMethod" ((Mapping Pos -> Parser HTMLMathMethod)
-> Node Pos -> Parser HTMLMathMethod)
-> (Mapping Pos -> Parser HTMLMathMethod)
-> Node Pos
-> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ \Mapping Pos
m -> do
Text
method <- Mapping Pos
m Mapping Pos -> Text -> Parser Text
forall a. FromYAML a => Mapping Pos -> Text -> Parser a
.: Text
"method"
Maybe Text
mburl <- Mapping Pos
m Mapping Pos -> Text -> Parser (Maybe Text)
forall a. FromYAML a => Mapping Pos -> Text -> Parser (Maybe a)
.:? Text
"url"
case Text
method :: Text of
Text
"plain" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
PlainMath
Text
"webtex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMathMethod -> Parser HTMLMathMethod)
-> HTMLMathMethod -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ Text -> HTMLMathMethod
WebTeX (Text -> HTMLMathMethod) -> Text -> HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" Maybe Text
mburl
Text
"gladtex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
GladTeX
Text
"mathml" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
MathML
Text
"mathjax" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMathMethod -> Parser HTMLMathMethod)
-> HTMLMathMethod -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ Text -> HTMLMathMethod
MathJax (Text -> HTMLMathMethod) -> Text -> HTMLMathMethod
forall a b. (a -> b) -> a -> b
$
Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
defaultMathJaxURL Maybe Text
mburl
Text
"katex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMathMethod -> Parser HTMLMathMethod)
-> HTMLMathMethod -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ Text -> HTMLMathMethod
KaTeX (Text -> HTMLMathMethod) -> Text -> HTMLMathMethod
forall a b. (a -> b) -> a -> b
$
Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
defaultKaTeXURL Maybe Text
mburl
Text
_ -> String -> Parser HTMLMathMethod
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser HTMLMathMethod)
-> String -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ String
"Unknown HTML math method " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
method) Node Pos
node
Parser HTMLMathMethod
-> Parser HTMLMathMethod -> Parser HTMLMathMethod
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String
-> (Text -> Parser HTMLMathMethod)
-> Node Pos
-> Parser HTMLMathMethod
forall a. String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr String
"HTMLMathMethod" ((Text -> Parser HTMLMathMethod)
-> Node Pos -> Parser HTMLMathMethod)
-> (Text -> Parser HTMLMathMethod)
-> Node Pos
-> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ \Text
method ->
case Text
method of
Text
"plain" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
PlainMath
Text
"webtex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMathMethod -> Parser HTMLMathMethod)
-> HTMLMathMethod -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ Text -> HTMLMathMethod
WebTeX Text
""
Text
"gladtex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
GladTeX
Text
"mathml" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
MathML
Text
"mathjax" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMathMethod -> Parser HTMLMathMethod)
-> HTMLMathMethod -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ Text -> HTMLMathMethod
MathJax Text
defaultMathJaxURL
Text
"katex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMathMethod -> Parser HTMLMathMethod)
-> HTMLMathMethod -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ Text -> HTMLMathMethod
KaTeX Text
defaultKaTeXURL
Text
_ -> String -> Parser HTMLMathMethod
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser HTMLMathMethod)
-> String -> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ String
"Unknown HTML math method " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
method) Node Pos
node
data CiteMethod = Citeproc
| Natbib
| Biblatex
deriving (Int -> CiteMethod -> ShowS
[CiteMethod] -> ShowS
CiteMethod -> String
(Int -> CiteMethod -> ShowS)
-> (CiteMethod -> String)
-> ([CiteMethod] -> ShowS)
-> Show CiteMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CiteMethod] -> ShowS
$cshowList :: [CiteMethod] -> ShowS
show :: CiteMethod -> String
$cshow :: CiteMethod -> String
showsPrec :: Int -> CiteMethod -> ShowS
$cshowsPrec :: Int -> CiteMethod -> ShowS
Show, ReadPrec [CiteMethod]
ReadPrec CiteMethod
Int -> ReadS CiteMethod
ReadS [CiteMethod]
(Int -> ReadS CiteMethod)
-> ReadS [CiteMethod]
-> ReadPrec CiteMethod
-> ReadPrec [CiteMethod]
-> Read CiteMethod
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CiteMethod]
$creadListPrec :: ReadPrec [CiteMethod]
readPrec :: ReadPrec CiteMethod
$creadPrec :: ReadPrec CiteMethod
readList :: ReadS [CiteMethod]
$creadList :: ReadS [CiteMethod]
readsPrec :: Int -> ReadS CiteMethod
$creadsPrec :: Int -> ReadS CiteMethod
Read, CiteMethod -> CiteMethod -> Bool
(CiteMethod -> CiteMethod -> Bool)
-> (CiteMethod -> CiteMethod -> Bool) -> Eq CiteMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CiteMethod -> CiteMethod -> Bool
$c/= :: CiteMethod -> CiteMethod -> Bool
== :: CiteMethod -> CiteMethod -> Bool
$c== :: CiteMethod -> CiteMethod -> Bool
Eq, Typeable CiteMethod
DataType
Constr
Typeable CiteMethod
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CiteMethod -> c CiteMethod)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CiteMethod)
-> (CiteMethod -> Constr)
-> (CiteMethod -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CiteMethod))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CiteMethod))
-> ((forall b. Data b => b -> b) -> CiteMethod -> CiteMethod)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r)
-> (forall u. (forall d. Data d => d -> u) -> CiteMethod -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CiteMethod -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod)
-> Data CiteMethod
CiteMethod -> DataType
CiteMethod -> Constr
(forall b. Data b => b -> b) -> CiteMethod -> CiteMethod
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CiteMethod -> c CiteMethod
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CiteMethod
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) -> CiteMethod -> u
forall u. (forall d. Data d => d -> u) -> CiteMethod -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CiteMethod
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CiteMethod -> c CiteMethod
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CiteMethod)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteMethod)
$cBiblatex :: Constr
$cNatbib :: Constr
$cCiteproc :: Constr
$tCiteMethod :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
gmapMp :: (forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
gmapM :: (forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
gmapQi :: Int -> (forall d. Data d => d -> u) -> CiteMethod -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CiteMethod -> u
gmapQ :: (forall d. Data d => d -> u) -> CiteMethod -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CiteMethod -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
gmapT :: (forall b. Data b => b -> b) -> CiteMethod -> CiteMethod
$cgmapT :: (forall b. Data b => b -> b) -> CiteMethod -> CiteMethod
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteMethod)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c CiteMethod)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CiteMethod)
dataTypeOf :: CiteMethod -> DataType
$cdataTypeOf :: CiteMethod -> DataType
toConstr :: CiteMethod -> Constr
$ctoConstr :: CiteMethod -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CiteMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CiteMethod
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CiteMethod -> c CiteMethod
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CiteMethod -> c CiteMethod
$cp1Data :: Typeable CiteMethod
Data, Typeable, (forall x. CiteMethod -> Rep CiteMethod x)
-> (forall x. Rep CiteMethod x -> CiteMethod) -> Generic CiteMethod
forall x. Rep CiteMethod x -> CiteMethod
forall x. CiteMethod -> Rep CiteMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CiteMethod x -> CiteMethod
$cfrom :: forall x. CiteMethod -> Rep CiteMethod x
Generic)
instance FromYAML CiteMethod where
parseYAML :: Node Pos -> Parser CiteMethod
parseYAML = String
-> (Text -> Parser CiteMethod) -> Node Pos -> Parser CiteMethod
forall a. String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr String
"Citeproc" ((Text -> Parser CiteMethod) -> Node Pos -> Parser CiteMethod)
-> (Text -> Parser CiteMethod) -> Node Pos -> Parser CiteMethod
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text
t of
Text
"citeproc" -> CiteMethod -> Parser CiteMethod
forall (m :: * -> *) a. Monad m => a -> m a
return CiteMethod
Citeproc
Text
"natbib" -> CiteMethod -> Parser CiteMethod
forall (m :: * -> *) a. Monad m => a -> m a
return CiteMethod
Natbib
Text
"biblatex" -> CiteMethod -> Parser CiteMethod
forall (m :: * -> *) a. Monad m => a -> m a
return CiteMethod
Biblatex
Text
_ -> String -> Parser CiteMethod
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser CiteMethod) -> String -> Parser CiteMethod
forall a b. (a -> b) -> a -> b
$ String
"Unknown citation method " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
data ObfuscationMethod = NoObfuscation
| ReferenceObfuscation
| JavascriptObfuscation
deriving (Int -> ObfuscationMethod -> ShowS
[ObfuscationMethod] -> ShowS
ObfuscationMethod -> String
(Int -> ObfuscationMethod -> ShowS)
-> (ObfuscationMethod -> String)
-> ([ObfuscationMethod] -> ShowS)
-> Show ObfuscationMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObfuscationMethod] -> ShowS
$cshowList :: [ObfuscationMethod] -> ShowS
show :: ObfuscationMethod -> String
$cshow :: ObfuscationMethod -> String
showsPrec :: Int -> ObfuscationMethod -> ShowS
$cshowsPrec :: Int -> ObfuscationMethod -> ShowS
Show, ReadPrec [ObfuscationMethod]
ReadPrec ObfuscationMethod
Int -> ReadS ObfuscationMethod
ReadS [ObfuscationMethod]
(Int -> ReadS ObfuscationMethod)
-> ReadS [ObfuscationMethod]
-> ReadPrec ObfuscationMethod
-> ReadPrec [ObfuscationMethod]
-> Read ObfuscationMethod
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObfuscationMethod]
$creadListPrec :: ReadPrec [ObfuscationMethod]
readPrec :: ReadPrec ObfuscationMethod
$creadPrec :: ReadPrec ObfuscationMethod
readList :: ReadS [ObfuscationMethod]
$creadList :: ReadS [ObfuscationMethod]
readsPrec :: Int -> ReadS ObfuscationMethod
$creadsPrec :: Int -> ReadS ObfuscationMethod
Read, ObfuscationMethod -> ObfuscationMethod -> Bool
(ObfuscationMethod -> ObfuscationMethod -> Bool)
-> (ObfuscationMethod -> ObfuscationMethod -> Bool)
-> Eq ObfuscationMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObfuscationMethod -> ObfuscationMethod -> Bool
$c/= :: ObfuscationMethod -> ObfuscationMethod -> Bool
== :: ObfuscationMethod -> ObfuscationMethod -> Bool
$c== :: ObfuscationMethod -> ObfuscationMethod -> Bool
Eq, Typeable ObfuscationMethod
DataType
Constr
Typeable ObfuscationMethod
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ObfuscationMethod
-> c ObfuscationMethod)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ObfuscationMethod)
-> (ObfuscationMethod -> Constr)
-> (ObfuscationMethod -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ObfuscationMethod))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ObfuscationMethod))
-> ((forall b. Data b => b -> b)
-> ObfuscationMethod -> ObfuscationMethod)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ObfuscationMethod -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ObfuscationMethod -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod)
-> Data ObfuscationMethod
ObfuscationMethod -> DataType
ObfuscationMethod -> Constr
(forall b. Data b => b -> b)
-> ObfuscationMethod -> ObfuscationMethod
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ObfuscationMethod -> c ObfuscationMethod
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ObfuscationMethod
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) -> ObfuscationMethod -> u
forall u. (forall d. Data d => d -> u) -> ObfuscationMethod -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ObfuscationMethod
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ObfuscationMethod -> c ObfuscationMethod
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ObfuscationMethod)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ObfuscationMethod)
$cJavascriptObfuscation :: Constr
$cReferenceObfuscation :: Constr
$cNoObfuscation :: Constr
$tObfuscationMethod :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
gmapMp :: (forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
gmapM :: (forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
gmapQi :: Int -> (forall d. Data d => d -> u) -> ObfuscationMethod -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ObfuscationMethod -> u
gmapQ :: (forall d. Data d => d -> u) -> ObfuscationMethod -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ObfuscationMethod -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
gmapT :: (forall b. Data b => b -> b)
-> ObfuscationMethod -> ObfuscationMethod
$cgmapT :: (forall b. Data b => b -> b)
-> ObfuscationMethod -> ObfuscationMethod
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ObfuscationMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ObfuscationMethod)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ObfuscationMethod)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ObfuscationMethod)
dataTypeOf :: ObfuscationMethod -> DataType
$cdataTypeOf :: ObfuscationMethod -> DataType
toConstr :: ObfuscationMethod -> Constr
$ctoConstr :: ObfuscationMethod -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ObfuscationMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ObfuscationMethod
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ObfuscationMethod -> c ObfuscationMethod
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ObfuscationMethod -> c ObfuscationMethod
$cp1Data :: Typeable ObfuscationMethod
Data, Typeable, (forall x. ObfuscationMethod -> Rep ObfuscationMethod x)
-> (forall x. Rep ObfuscationMethod x -> ObfuscationMethod)
-> Generic ObfuscationMethod
forall x. Rep ObfuscationMethod x -> ObfuscationMethod
forall x. ObfuscationMethod -> Rep ObfuscationMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ObfuscationMethod x -> ObfuscationMethod
$cfrom :: forall x. ObfuscationMethod -> Rep ObfuscationMethod x
Generic)
instance FromYAML ObfuscationMethod where
parseYAML :: Node Pos -> Parser ObfuscationMethod
parseYAML = String
-> (Text -> Parser ObfuscationMethod)
-> Node Pos
-> Parser ObfuscationMethod
forall a. String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr String
"Citeproc" ((Text -> Parser ObfuscationMethod)
-> Node Pos -> Parser ObfuscationMethod)
-> (Text -> Parser ObfuscationMethod)
-> Node Pos
-> Parser ObfuscationMethod
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text
t of
Text
"none" -> ObfuscationMethod -> Parser ObfuscationMethod
forall (m :: * -> *) a. Monad m => a -> m a
return ObfuscationMethod
NoObfuscation
Text
"references" -> ObfuscationMethod -> Parser ObfuscationMethod
forall (m :: * -> *) a. Monad m => a -> m a
return ObfuscationMethod
ReferenceObfuscation
Text
"javascript" -> ObfuscationMethod -> Parser ObfuscationMethod
forall (m :: * -> *) a. Monad m => a -> m a
return ObfuscationMethod
JavascriptObfuscation
Text
_ -> String -> Parser ObfuscationMethod
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ObfuscationMethod)
-> String -> Parser ObfuscationMethod
forall a b. (a -> b) -> a -> b
$ String
"Unknown obfuscation method " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
data HTMLSlideVariant = S5Slides
| SlidySlides
| SlideousSlides
| DZSlides
| RevealJsSlides
| NoSlides
deriving (Int -> HTMLSlideVariant -> ShowS
[HTMLSlideVariant] -> ShowS
HTMLSlideVariant -> String
(Int -> HTMLSlideVariant -> ShowS)
-> (HTMLSlideVariant -> String)
-> ([HTMLSlideVariant] -> ShowS)
-> Show HTMLSlideVariant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HTMLSlideVariant] -> ShowS
$cshowList :: [HTMLSlideVariant] -> ShowS
show :: HTMLSlideVariant -> String
$cshow :: HTMLSlideVariant -> String
showsPrec :: Int -> HTMLSlideVariant -> ShowS
$cshowsPrec :: Int -> HTMLSlideVariant -> ShowS
Show, ReadPrec [HTMLSlideVariant]
ReadPrec HTMLSlideVariant
Int -> ReadS HTMLSlideVariant
ReadS [HTMLSlideVariant]
(Int -> ReadS HTMLSlideVariant)
-> ReadS [HTMLSlideVariant]
-> ReadPrec HTMLSlideVariant
-> ReadPrec [HTMLSlideVariant]
-> Read HTMLSlideVariant
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HTMLSlideVariant]
$creadListPrec :: ReadPrec [HTMLSlideVariant]
readPrec :: ReadPrec HTMLSlideVariant
$creadPrec :: ReadPrec HTMLSlideVariant
readList :: ReadS [HTMLSlideVariant]
$creadList :: ReadS [HTMLSlideVariant]
readsPrec :: Int -> ReadS HTMLSlideVariant
$creadsPrec :: Int -> ReadS HTMLSlideVariant
Read, HTMLSlideVariant -> HTMLSlideVariant -> Bool
(HTMLSlideVariant -> HTMLSlideVariant -> Bool)
-> (HTMLSlideVariant -> HTMLSlideVariant -> Bool)
-> Eq HTMLSlideVariant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
$c/= :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
== :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
$c== :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
Eq, Typeable HTMLSlideVariant
DataType
Constr
Typeable HTMLSlideVariant
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant)
-> (HTMLSlideVariant -> Constr)
-> (HTMLSlideVariant -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLSlideVariant))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLSlideVariant))
-> ((forall b. Data b => b -> b)
-> HTMLSlideVariant -> HTMLSlideVariant)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r)
-> (forall u.
(forall d. Data d => d -> u) -> HTMLSlideVariant -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> HTMLSlideVariant -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant)
-> Data HTMLSlideVariant
HTMLSlideVariant -> DataType
HTMLSlideVariant -> Constr
(forall b. Data b => b -> b)
-> HTMLSlideVariant -> HTMLSlideVariant
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant
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) -> HTMLSlideVariant -> u
forall u. (forall d. Data d => d -> u) -> HTMLSlideVariant -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLSlideVariant)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLSlideVariant)
$cNoSlides :: Constr
$cRevealJsSlides :: Constr
$cDZSlides :: Constr
$cSlideousSlides :: Constr
$cSlidySlides :: Constr
$cS5Slides :: Constr
$tHTMLSlideVariant :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
gmapMp :: (forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
gmapM :: (forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
gmapQi :: Int -> (forall d. Data d => d -> u) -> HTMLSlideVariant -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HTMLSlideVariant -> u
gmapQ :: (forall d. Data d => d -> u) -> HTMLSlideVariant -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HTMLSlideVariant -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
gmapT :: (forall b. Data b => b -> b)
-> HTMLSlideVariant -> HTMLSlideVariant
$cgmapT :: (forall b. Data b => b -> b)
-> HTMLSlideVariant -> HTMLSlideVariant
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLSlideVariant)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLSlideVariant)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c HTMLSlideVariant)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLSlideVariant)
dataTypeOf :: HTMLSlideVariant -> DataType
$cdataTypeOf :: HTMLSlideVariant -> DataType
toConstr :: HTMLSlideVariant -> Constr
$ctoConstr :: HTMLSlideVariant -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant
$cp1Data :: Typeable HTMLSlideVariant
Data, Typeable, (forall x. HTMLSlideVariant -> Rep HTMLSlideVariant x)
-> (forall x. Rep HTMLSlideVariant x -> HTMLSlideVariant)
-> Generic HTMLSlideVariant
forall x. Rep HTMLSlideVariant x -> HTMLSlideVariant
forall x. HTMLSlideVariant -> Rep HTMLSlideVariant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HTMLSlideVariant x -> HTMLSlideVariant
$cfrom :: forall x. HTMLSlideVariant -> Rep HTMLSlideVariant x
Generic)
data TrackChanges = AcceptChanges
| RejectChanges
| AllChanges
deriving (Int -> TrackChanges -> ShowS
[TrackChanges] -> ShowS
TrackChanges -> String
(Int -> TrackChanges -> ShowS)
-> (TrackChanges -> String)
-> ([TrackChanges] -> ShowS)
-> Show TrackChanges
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrackChanges] -> ShowS
$cshowList :: [TrackChanges] -> ShowS
show :: TrackChanges -> String
$cshow :: TrackChanges -> String
showsPrec :: Int -> TrackChanges -> ShowS
$cshowsPrec :: Int -> TrackChanges -> ShowS
Show, ReadPrec [TrackChanges]
ReadPrec TrackChanges
Int -> ReadS TrackChanges
ReadS [TrackChanges]
(Int -> ReadS TrackChanges)
-> ReadS [TrackChanges]
-> ReadPrec TrackChanges
-> ReadPrec [TrackChanges]
-> Read TrackChanges
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TrackChanges]
$creadListPrec :: ReadPrec [TrackChanges]
readPrec :: ReadPrec TrackChanges
$creadPrec :: ReadPrec TrackChanges
readList :: ReadS [TrackChanges]
$creadList :: ReadS [TrackChanges]
readsPrec :: Int -> ReadS TrackChanges
$creadsPrec :: Int -> ReadS TrackChanges
Read, TrackChanges -> TrackChanges -> Bool
(TrackChanges -> TrackChanges -> Bool)
-> (TrackChanges -> TrackChanges -> Bool) -> Eq TrackChanges
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrackChanges -> TrackChanges -> Bool
$c/= :: TrackChanges -> TrackChanges -> Bool
== :: TrackChanges -> TrackChanges -> Bool
$c== :: TrackChanges -> TrackChanges -> Bool
Eq, Typeable TrackChanges
DataType
Constr
Typeable TrackChanges
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TrackChanges -> c TrackChanges)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TrackChanges)
-> (TrackChanges -> Constr)
-> (TrackChanges -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TrackChanges))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TrackChanges))
-> ((forall b. Data b => b -> b) -> TrackChanges -> TrackChanges)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r)
-> (forall u. (forall d. Data d => d -> u) -> TrackChanges -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TrackChanges -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges)
-> Data TrackChanges
TrackChanges -> DataType
TrackChanges -> Constr
(forall b. Data b => b -> b) -> TrackChanges -> TrackChanges
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TrackChanges -> c TrackChanges
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TrackChanges
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) -> TrackChanges -> u
forall u. (forall d. Data d => d -> u) -> TrackChanges -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TrackChanges
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TrackChanges -> c TrackChanges
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TrackChanges)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TrackChanges)
$cAllChanges :: Constr
$cRejectChanges :: Constr
$cAcceptChanges :: Constr
$tTrackChanges :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
gmapMp :: (forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
gmapM :: (forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
gmapQi :: Int -> (forall d. Data d => d -> u) -> TrackChanges -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TrackChanges -> u
gmapQ :: (forall d. Data d => d -> u) -> TrackChanges -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TrackChanges -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
gmapT :: (forall b. Data b => b -> b) -> TrackChanges -> TrackChanges
$cgmapT :: (forall b. Data b => b -> b) -> TrackChanges -> TrackChanges
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TrackChanges)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TrackChanges)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TrackChanges)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TrackChanges)
dataTypeOf :: TrackChanges -> DataType
$cdataTypeOf :: TrackChanges -> DataType
toConstr :: TrackChanges -> Constr
$ctoConstr :: TrackChanges -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TrackChanges
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TrackChanges
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TrackChanges -> c TrackChanges
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TrackChanges -> c TrackChanges
$cp1Data :: Typeable TrackChanges
Data, Typeable, (forall x. TrackChanges -> Rep TrackChanges x)
-> (forall x. Rep TrackChanges x -> TrackChanges)
-> Generic TrackChanges
forall x. Rep TrackChanges x -> TrackChanges
forall x. TrackChanges -> Rep TrackChanges x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TrackChanges x -> TrackChanges
$cfrom :: forall x. TrackChanges -> Rep TrackChanges x
Generic)
instance FromYAML TrackChanges where
parseYAML :: Node Pos -> Parser TrackChanges
parseYAML = String
-> (Text -> Parser TrackChanges) -> Node Pos -> Parser TrackChanges
forall a. String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr String
"TrackChanges" ((Text -> Parser TrackChanges) -> Node Pos -> Parser TrackChanges)
-> (Text -> Parser TrackChanges) -> Node Pos -> Parser TrackChanges
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text
t of
Text
"accept" -> TrackChanges -> Parser TrackChanges
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
AcceptChanges
Text
"reject" -> TrackChanges -> Parser TrackChanges
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
RejectChanges
Text
"all" -> TrackChanges -> Parser TrackChanges
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
AllChanges
Text
_ -> String -> Parser TrackChanges
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser TrackChanges) -> String -> Parser TrackChanges
forall a b. (a -> b) -> a -> b
$ String
"Unknown track changes method " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
data WrapOption = WrapAuto
| WrapNone
| WrapPreserve
deriving (Int -> WrapOption -> ShowS
[WrapOption] -> ShowS
WrapOption -> String
(Int -> WrapOption -> ShowS)
-> (WrapOption -> String)
-> ([WrapOption] -> ShowS)
-> Show WrapOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WrapOption] -> ShowS
$cshowList :: [WrapOption] -> ShowS
show :: WrapOption -> String
$cshow :: WrapOption -> String
showsPrec :: Int -> WrapOption -> ShowS
$cshowsPrec :: Int -> WrapOption -> ShowS
Show, ReadPrec [WrapOption]
ReadPrec WrapOption
Int -> ReadS WrapOption
ReadS [WrapOption]
(Int -> ReadS WrapOption)
-> ReadS [WrapOption]
-> ReadPrec WrapOption
-> ReadPrec [WrapOption]
-> Read WrapOption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WrapOption]
$creadListPrec :: ReadPrec [WrapOption]
readPrec :: ReadPrec WrapOption
$creadPrec :: ReadPrec WrapOption
readList :: ReadS [WrapOption]
$creadList :: ReadS [WrapOption]
readsPrec :: Int -> ReadS WrapOption
$creadsPrec :: Int -> ReadS WrapOption
Read, WrapOption -> WrapOption -> Bool
(WrapOption -> WrapOption -> Bool)
-> (WrapOption -> WrapOption -> Bool) -> Eq WrapOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WrapOption -> WrapOption -> Bool
$c/= :: WrapOption -> WrapOption -> Bool
== :: WrapOption -> WrapOption -> Bool
$c== :: WrapOption -> WrapOption -> Bool
Eq, Typeable WrapOption
DataType
Constr
Typeable WrapOption
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapOption -> c WrapOption)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WrapOption)
-> (WrapOption -> Constr)
-> (WrapOption -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WrapOption))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WrapOption))
-> ((forall b. Data b => b -> b) -> WrapOption -> WrapOption)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r)
-> (forall u. (forall d. Data d => d -> u) -> WrapOption -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> WrapOption -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption)
-> Data WrapOption
WrapOption -> DataType
WrapOption -> Constr
(forall b. Data b => b -> b) -> WrapOption -> WrapOption
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapOption -> c WrapOption
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WrapOption
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) -> WrapOption -> u
forall u. (forall d. Data d => d -> u) -> WrapOption -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WrapOption
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapOption -> c WrapOption
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WrapOption)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WrapOption)
$cWrapPreserve :: Constr
$cWrapNone :: Constr
$cWrapAuto :: Constr
$tWrapOption :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
gmapMp :: (forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
gmapM :: (forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
gmapQi :: Int -> (forall d. Data d => d -> u) -> WrapOption -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WrapOption -> u
gmapQ :: (forall d. Data d => d -> u) -> WrapOption -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WrapOption -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
gmapT :: (forall b. Data b => b -> b) -> WrapOption -> WrapOption
$cgmapT :: (forall b. Data b => b -> b) -> WrapOption -> WrapOption
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WrapOption)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WrapOption)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c WrapOption)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WrapOption)
dataTypeOf :: WrapOption -> DataType
$cdataTypeOf :: WrapOption -> DataType
toConstr :: WrapOption -> Constr
$ctoConstr :: WrapOption -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WrapOption
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WrapOption
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapOption -> c WrapOption
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapOption -> c WrapOption
$cp1Data :: Typeable WrapOption
Data, Typeable, (forall x. WrapOption -> Rep WrapOption x)
-> (forall x. Rep WrapOption x -> WrapOption) -> Generic WrapOption
forall x. Rep WrapOption x -> WrapOption
forall x. WrapOption -> Rep WrapOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WrapOption x -> WrapOption
$cfrom :: forall x. WrapOption -> Rep WrapOption x
Generic)
instance FromYAML WrapOption where
parseYAML :: Node Pos -> Parser WrapOption
parseYAML = String
-> (Text -> Parser WrapOption) -> Node Pos -> Parser WrapOption
forall a. String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr String
"WrapOption" ((Text -> Parser WrapOption) -> Node Pos -> Parser WrapOption)
-> (Text -> Parser WrapOption) -> Node Pos -> Parser WrapOption
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text
t of
Text
"auto" -> WrapOption -> Parser WrapOption
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapAuto
Text
"none" -> WrapOption -> Parser WrapOption
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapNone
Text
"preserve" -> WrapOption -> Parser WrapOption
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapPreserve
Text
_ -> String -> Parser WrapOption
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser WrapOption) -> String -> Parser WrapOption
forall a b. (a -> b) -> a -> b
$ String
"Unknown wrap method " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
data TopLevelDivision = TopLevelPart
| TopLevelChapter
| TopLevelSection
| TopLevelDefault
deriving (Int -> TopLevelDivision -> ShowS
[TopLevelDivision] -> ShowS
TopLevelDivision -> String
(Int -> TopLevelDivision -> ShowS)
-> (TopLevelDivision -> String)
-> ([TopLevelDivision] -> ShowS)
-> Show TopLevelDivision
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TopLevelDivision] -> ShowS
$cshowList :: [TopLevelDivision] -> ShowS
show :: TopLevelDivision -> String
$cshow :: TopLevelDivision -> String
showsPrec :: Int -> TopLevelDivision -> ShowS
$cshowsPrec :: Int -> TopLevelDivision -> ShowS
Show, ReadPrec [TopLevelDivision]
ReadPrec TopLevelDivision
Int -> ReadS TopLevelDivision
ReadS [TopLevelDivision]
(Int -> ReadS TopLevelDivision)
-> ReadS [TopLevelDivision]
-> ReadPrec TopLevelDivision
-> ReadPrec [TopLevelDivision]
-> Read TopLevelDivision
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TopLevelDivision]
$creadListPrec :: ReadPrec [TopLevelDivision]
readPrec :: ReadPrec TopLevelDivision
$creadPrec :: ReadPrec TopLevelDivision
readList :: ReadS [TopLevelDivision]
$creadList :: ReadS [TopLevelDivision]
readsPrec :: Int -> ReadS TopLevelDivision
$creadsPrec :: Int -> ReadS TopLevelDivision
Read, TopLevelDivision -> TopLevelDivision -> Bool
(TopLevelDivision -> TopLevelDivision -> Bool)
-> (TopLevelDivision -> TopLevelDivision -> Bool)
-> Eq TopLevelDivision
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TopLevelDivision -> TopLevelDivision -> Bool
$c/= :: TopLevelDivision -> TopLevelDivision -> Bool
== :: TopLevelDivision -> TopLevelDivision -> Bool
$c== :: TopLevelDivision -> TopLevelDivision -> Bool
Eq, Typeable TopLevelDivision
DataType
Constr
Typeable TopLevelDivision
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelDivision)
-> (TopLevelDivision -> Constr)
-> (TopLevelDivision -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelDivision))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelDivision))
-> ((forall b. Data b => b -> b)
-> TopLevelDivision -> TopLevelDivision)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r)
-> (forall u.
(forall d. Data d => d -> u) -> TopLevelDivision -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TopLevelDivision -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision)
-> Data TopLevelDivision
TopLevelDivision -> DataType
TopLevelDivision -> Constr
(forall b. Data b => b -> b)
-> TopLevelDivision -> TopLevelDivision
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelDivision
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) -> TopLevelDivision -> u
forall u. (forall d. Data d => d -> u) -> TopLevelDivision -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelDivision
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelDivision)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelDivision)
$cTopLevelDefault :: Constr
$cTopLevelSection :: Constr
$cTopLevelChapter :: Constr
$cTopLevelPart :: Constr
$tTopLevelDivision :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
gmapMp :: (forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
gmapM :: (forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
gmapQi :: Int -> (forall d. Data d => d -> u) -> TopLevelDivision -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TopLevelDivision -> u
gmapQ :: (forall d. Data d => d -> u) -> TopLevelDivision -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TopLevelDivision -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
gmapT :: (forall b. Data b => b -> b)
-> TopLevelDivision -> TopLevelDivision
$cgmapT :: (forall b. Data b => b -> b)
-> TopLevelDivision -> TopLevelDivision
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelDivision)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelDivision)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TopLevelDivision)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelDivision)
dataTypeOf :: TopLevelDivision -> DataType
$cdataTypeOf :: TopLevelDivision -> DataType
toConstr :: TopLevelDivision -> Constr
$ctoConstr :: TopLevelDivision -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelDivision
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelDivision
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision
$cp1Data :: Typeable TopLevelDivision
Data, Typeable, (forall x. TopLevelDivision -> Rep TopLevelDivision x)
-> (forall x. Rep TopLevelDivision x -> TopLevelDivision)
-> Generic TopLevelDivision
forall x. Rep TopLevelDivision x -> TopLevelDivision
forall x. TopLevelDivision -> Rep TopLevelDivision x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TopLevelDivision x -> TopLevelDivision
$cfrom :: forall x. TopLevelDivision -> Rep TopLevelDivision x
Generic)
instance FromYAML TopLevelDivision where
parseYAML :: Node Pos -> Parser TopLevelDivision
parseYAML = String
-> (Text -> Parser TopLevelDivision)
-> Node Pos
-> Parser TopLevelDivision
forall a. String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr String
"TopLevelDivision" ((Text -> Parser TopLevelDivision)
-> Node Pos -> Parser TopLevelDivision)
-> (Text -> Parser TopLevelDivision)
-> Node Pos
-> Parser TopLevelDivision
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text
t of
Text
"part" -> TopLevelDivision -> Parser TopLevelDivision
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelPart
Text
"chapter" -> TopLevelDivision -> Parser TopLevelDivision
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelChapter
Text
"section" -> TopLevelDivision -> Parser TopLevelDivision
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelSection
Text
"default" -> TopLevelDivision -> Parser TopLevelDivision
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelDefault
Text
_ -> String -> Parser TopLevelDivision
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser TopLevelDivision)
-> String -> Parser TopLevelDivision
forall a b. (a -> b) -> a -> b
$ String
"Unknown top level division " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
data ReferenceLocation = EndOfBlock
| EndOfSection
| EndOfDocument
deriving (Int -> ReferenceLocation -> ShowS
[ReferenceLocation] -> ShowS
ReferenceLocation -> String
(Int -> ReferenceLocation -> ShowS)
-> (ReferenceLocation -> String)
-> ([ReferenceLocation] -> ShowS)
-> Show ReferenceLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReferenceLocation] -> ShowS
$cshowList :: [ReferenceLocation] -> ShowS
show :: ReferenceLocation -> String
$cshow :: ReferenceLocation -> String
showsPrec :: Int -> ReferenceLocation -> ShowS
$cshowsPrec :: Int -> ReferenceLocation -> ShowS
Show, ReadPrec [ReferenceLocation]
ReadPrec ReferenceLocation
Int -> ReadS ReferenceLocation
ReadS [ReferenceLocation]
(Int -> ReadS ReferenceLocation)
-> ReadS [ReferenceLocation]
-> ReadPrec ReferenceLocation
-> ReadPrec [ReferenceLocation]
-> Read ReferenceLocation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReferenceLocation]
$creadListPrec :: ReadPrec [ReferenceLocation]
readPrec :: ReadPrec ReferenceLocation
$creadPrec :: ReadPrec ReferenceLocation
readList :: ReadS [ReferenceLocation]
$creadList :: ReadS [ReferenceLocation]
readsPrec :: Int -> ReadS ReferenceLocation
$creadsPrec :: Int -> ReadS ReferenceLocation
Read, ReferenceLocation -> ReferenceLocation -> Bool
(ReferenceLocation -> ReferenceLocation -> Bool)
-> (ReferenceLocation -> ReferenceLocation -> Bool)
-> Eq ReferenceLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReferenceLocation -> ReferenceLocation -> Bool
$c/= :: ReferenceLocation -> ReferenceLocation -> Bool
== :: ReferenceLocation -> ReferenceLocation -> Bool
$c== :: ReferenceLocation -> ReferenceLocation -> Bool
Eq, Typeable ReferenceLocation
DataType
Constr
Typeable ReferenceLocation
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ReferenceLocation
-> c ReferenceLocation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceLocation)
-> (ReferenceLocation -> Constr)
-> (ReferenceLocation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceLocation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceLocation))
-> ((forall b. Data b => b -> b)
-> ReferenceLocation -> ReferenceLocation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ReferenceLocation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ReferenceLocation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation)
-> Data ReferenceLocation
ReferenceLocation -> DataType
ReferenceLocation -> Constr
(forall b. Data b => b -> b)
-> ReferenceLocation -> ReferenceLocation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceLocation -> c ReferenceLocation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceLocation
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) -> ReferenceLocation -> u
forall u. (forall d. Data d => d -> u) -> ReferenceLocation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceLocation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceLocation -> c ReferenceLocation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceLocation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceLocation)
$cEndOfDocument :: Constr
$cEndOfSection :: Constr
$cEndOfBlock :: Constr
$tReferenceLocation :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
gmapMp :: (forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
gmapM :: (forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
gmapQi :: Int -> (forall d. Data d => d -> u) -> ReferenceLocation -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ReferenceLocation -> u
gmapQ :: (forall d. Data d => d -> u) -> ReferenceLocation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReferenceLocation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
gmapT :: (forall b. Data b => b -> b)
-> ReferenceLocation -> ReferenceLocation
$cgmapT :: (forall b. Data b => b -> b)
-> ReferenceLocation -> ReferenceLocation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceLocation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceLocation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ReferenceLocation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceLocation)
dataTypeOf :: ReferenceLocation -> DataType
$cdataTypeOf :: ReferenceLocation -> DataType
toConstr :: ReferenceLocation -> Constr
$ctoConstr :: ReferenceLocation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceLocation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceLocation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceLocation -> c ReferenceLocation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceLocation -> c ReferenceLocation
$cp1Data :: Typeable ReferenceLocation
Data, Typeable, (forall x. ReferenceLocation -> Rep ReferenceLocation x)
-> (forall x. Rep ReferenceLocation x -> ReferenceLocation)
-> Generic ReferenceLocation
forall x. Rep ReferenceLocation x -> ReferenceLocation
forall x. ReferenceLocation -> Rep ReferenceLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReferenceLocation x -> ReferenceLocation
$cfrom :: forall x. ReferenceLocation -> Rep ReferenceLocation x
Generic)
instance FromYAML ReferenceLocation where
parseYAML :: Node Pos -> Parser ReferenceLocation
parseYAML = String
-> (Text -> Parser ReferenceLocation)
-> Node Pos
-> Parser ReferenceLocation
forall a. String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr String
"ReferenceLocation" ((Text -> Parser ReferenceLocation)
-> Node Pos -> Parser ReferenceLocation)
-> (Text -> Parser ReferenceLocation)
-> Node Pos
-> Parser ReferenceLocation
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text
t of
Text
"block" -> ReferenceLocation -> Parser ReferenceLocation
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfBlock
Text
"section" -> ReferenceLocation -> Parser ReferenceLocation
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfSection
Text
"document" -> ReferenceLocation -> Parser ReferenceLocation
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfDocument
Text
_ -> String -> Parser ReferenceLocation
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ReferenceLocation)
-> String -> Parser ReferenceLocation
forall a b. (a -> b) -> a -> b
$ String
"Unknown reference location " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
data WriterOptions = WriterOptions
{ WriterOptions -> Maybe (Template Text)
writerTemplate :: Maybe (Template Text)
, WriterOptions -> Context Text
writerVariables :: Context Text
, WriterOptions -> Int
writerTabStop :: Int
, WriterOptions -> Bool
writerTableOfContents :: Bool
, WriterOptions -> Bool
writerIncremental :: Bool
, WriterOptions -> HTMLMathMethod
writerHTMLMathMethod :: HTMLMathMethod
, WriterOptions -> Bool
writerNumberSections :: Bool
, WriterOptions -> [Int]
writerNumberOffset :: [Int]
, WriterOptions -> Bool
writerSectionDivs :: Bool
, WriterOptions -> Extensions
writerExtensions :: Extensions
, WriterOptions -> Bool
writerReferenceLinks :: Bool
, WriterOptions -> Int
writerDpi :: Int
, WriterOptions -> WrapOption
writerWrapText :: WrapOption
, WriterOptions -> Int
writerColumns :: Int
, WriterOptions -> ObfuscationMethod
writerEmailObfuscation :: ObfuscationMethod
, WriterOptions -> Text
writerIdentifierPrefix :: Text
, WriterOptions -> CiteMethod
writerCiteMethod :: CiteMethod
, WriterOptions -> Bool
writerHtmlQTags :: Bool
, WriterOptions -> Maybe Int
writerSlideLevel :: Maybe Int
, WriterOptions -> TopLevelDivision
writerTopLevelDivision :: TopLevelDivision
, WriterOptions -> Bool
writerListings :: Bool
, WriterOptions -> Maybe Style
writerHighlightStyle :: Maybe Style
, :: Bool
, WriterOptions -> Text
writerEpubSubdirectory :: Text
, WriterOptions -> Maybe Text
writerEpubMetadata :: Maybe Text
, WriterOptions -> [String]
writerEpubFonts :: [FilePath]
, WriterOptions -> Int
writerEpubChapterLevel :: Int
, WriterOptions -> Int
writerTOCDepth :: Int
, WriterOptions -> Maybe String
writerReferenceDoc :: Maybe FilePath
, WriterOptions -> ReferenceLocation
writerReferenceLocation :: ReferenceLocation
, WriterOptions -> SyntaxMap
writerSyntaxMap :: SyntaxMap
, WriterOptions -> Bool
writerPreferAscii :: Bool
} deriving (Int -> WriterOptions -> ShowS
[WriterOptions] -> ShowS
WriterOptions -> String
(Int -> WriterOptions -> ShowS)
-> (WriterOptions -> String)
-> ([WriterOptions] -> ShowS)
-> Show WriterOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WriterOptions] -> ShowS
$cshowList :: [WriterOptions] -> ShowS
show :: WriterOptions -> String
$cshow :: WriterOptions -> String
showsPrec :: Int -> WriterOptions -> ShowS
$cshowsPrec :: Int -> WriterOptions -> ShowS
Show, Typeable WriterOptions
DataType
Constr
Typeable WriterOptions
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WriterOptions -> c WriterOptions)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WriterOptions)
-> (WriterOptions -> Constr)
-> (WriterOptions -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WriterOptions))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WriterOptions))
-> ((forall b. Data b => b -> b) -> WriterOptions -> WriterOptions)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r)
-> (forall u. (forall d. Data d => d -> u) -> WriterOptions -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> WriterOptions -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions)
-> Data WriterOptions
WriterOptions -> DataType
WriterOptions -> Constr
(forall b. Data b => b -> b) -> WriterOptions -> WriterOptions
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WriterOptions -> c WriterOptions
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WriterOptions
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) -> WriterOptions -> u
forall u. (forall d. Data d => d -> u) -> WriterOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WriterOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WriterOptions -> c WriterOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WriterOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WriterOptions)
$cWriterOptions :: Constr
$tWriterOptions :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
gmapMp :: (forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
gmapM :: (forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
gmapQi :: Int -> (forall d. Data d => d -> u) -> WriterOptions -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WriterOptions -> u
gmapQ :: (forall d. Data d => d -> u) -> WriterOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WriterOptions -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
gmapT :: (forall b. Data b => b -> b) -> WriterOptions -> WriterOptions
$cgmapT :: (forall b. Data b => b -> b) -> WriterOptions -> WriterOptions
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WriterOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WriterOptions)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c WriterOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WriterOptions)
dataTypeOf :: WriterOptions -> DataType
$cdataTypeOf :: WriterOptions -> DataType
toConstr :: WriterOptions -> Constr
$ctoConstr :: WriterOptions -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WriterOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WriterOptions
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WriterOptions -> c WriterOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WriterOptions -> c WriterOptions
$cp1Data :: Typeable WriterOptions
Data, Typeable, (forall x. WriterOptions -> Rep WriterOptions x)
-> (forall x. Rep WriterOptions x -> WriterOptions)
-> Generic WriterOptions
forall x. Rep WriterOptions x -> WriterOptions
forall x. WriterOptions -> Rep WriterOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WriterOptions x -> WriterOptions
$cfrom :: forall x. WriterOptions -> Rep WriterOptions x
Generic)
instance Default WriterOptions where
def :: WriterOptions
def = WriterOptions :: Maybe (Template Text)
-> Context Text
-> Int
-> Bool
-> Bool
-> HTMLMathMethod
-> Bool
-> [Int]
-> Bool
-> Extensions
-> Bool
-> Int
-> WrapOption
-> Int
-> ObfuscationMethod
-> Text
-> CiteMethod
-> Bool
-> Maybe Int
-> TopLevelDivision
-> Bool
-> Maybe Style
-> Bool
-> Text
-> Maybe Text
-> [String]
-> Int
-> Int
-> Maybe String
-> ReferenceLocation
-> SyntaxMap
-> Bool
-> WriterOptions
WriterOptions { writerTemplate :: Maybe (Template Text)
writerTemplate = Maybe (Template Text)
forall a. Maybe a
Nothing
, writerVariables :: Context Text
writerVariables = Context Text
forall a. Monoid a => a
mempty
, writerTabStop :: Int
writerTabStop = Int
4
, writerTableOfContents :: Bool
writerTableOfContents = Bool
False
, writerIncremental :: Bool
writerIncremental = Bool
False
, writerHTMLMathMethod :: HTMLMathMethod
writerHTMLMathMethod = HTMLMathMethod
PlainMath
, writerNumberSections :: Bool
writerNumberSections = Bool
False
, writerNumberOffset :: [Int]
writerNumberOffset = [Int
0,Int
0,Int
0,Int
0,Int
0,Int
0]
, writerSectionDivs :: Bool
writerSectionDivs = Bool
False
, writerExtensions :: Extensions
writerExtensions = Extensions
emptyExtensions
, writerReferenceLinks :: Bool
writerReferenceLinks = Bool
False
, writerDpi :: Int
writerDpi = Int
96
, writerWrapText :: WrapOption
writerWrapText = WrapOption
WrapAuto
, writerColumns :: Int
writerColumns = Int
72
, writerEmailObfuscation :: ObfuscationMethod
writerEmailObfuscation = ObfuscationMethod
NoObfuscation
, writerIdentifierPrefix :: Text
writerIdentifierPrefix = Text
""
, writerCiteMethod :: CiteMethod
writerCiteMethod = CiteMethod
Citeproc
, writerHtmlQTags :: Bool
writerHtmlQTags = Bool
False
, writerSlideLevel :: Maybe Int
writerSlideLevel = Maybe Int
forall a. Maybe a
Nothing
, writerTopLevelDivision :: TopLevelDivision
writerTopLevelDivision = TopLevelDivision
TopLevelDefault
, writerListings :: Bool
writerListings = Bool
False
, writerHighlightStyle :: Maybe Style
writerHighlightStyle = Style -> Maybe Style
forall a. a -> Maybe a
Just Style
pygments
, writerSetextHeaders :: Bool
writerSetextHeaders = Bool
False
, writerEpubSubdirectory :: Text
writerEpubSubdirectory = Text
"EPUB"
, writerEpubMetadata :: Maybe Text
writerEpubMetadata = Maybe Text
forall a. Maybe a
Nothing
, writerEpubFonts :: [String]
writerEpubFonts = []
, writerEpubChapterLevel :: Int
writerEpubChapterLevel = Int
1
, writerTOCDepth :: Int
writerTOCDepth = Int
3
, writerReferenceDoc :: Maybe String
writerReferenceDoc = Maybe String
forall a. Maybe a
Nothing
, writerReferenceLocation :: ReferenceLocation
writerReferenceLocation = ReferenceLocation
EndOfDocument
, writerSyntaxMap :: SyntaxMap
writerSyntaxMap = SyntaxMap
defaultSyntaxMap
, writerPreferAscii :: Bool
writerPreferAscii = Bool
False
}
instance HasSyntaxExtensions WriterOptions where
getExtensions :: WriterOptions -> Extensions
getExtensions WriterOptions
opts = WriterOptions -> Extensions
writerExtensions WriterOptions
opts
isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled :: Extension -> a -> Bool
isEnabled Extension
ext a
opts = Extension
ext Extension -> Extensions -> Bool
`extensionEnabled` a -> Extensions
forall a. HasSyntaxExtensions a => a -> Extensions
getExtensions a
opts
defaultMathJaxURL :: Text
defaultMathJaxURL :: Text
defaultMathJaxURL = Text
"https://cdn.jsdelivr.net/npm/mathjax@3/es5/tex-chtml-full.js"
defaultKaTeXURL :: Text
defaultKaTeXURL :: Text
defaultKaTeXURL = Text
"https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.11.1/"
$(deriveJSON defaultOptions ''ReaderOptions)
$(deriveJSON defaultOptions{
constructorTagModifier = map toLower,
sumEncoding = TaggedObject{
tagFieldName = "method",
contentsFieldName = "url" }
} ''HTMLMathMethod)
$(deriveJSON defaultOptions{ constructorTagModifier =
camelCaseStrToHyphenated
} ''CiteMethod)
$(deriveJSON defaultOptions{ constructorTagModifier =
\case
"NoObfuscation" -> "none"
"ReferenceObfuscation" -> "references"
"JavascriptObfuscation" -> "javascript"
_ -> "none"
} ''ObfuscationMethod)
$(deriveJSON defaultOptions ''HTMLSlideVariant)
$(deriveJSON defaultOptions{ constructorTagModifier =
camelCaseStrToHyphenated
} ''TrackChanges)
$(deriveJSON defaultOptions{ constructorTagModifier =
camelCaseStrToHyphenated
} ''WrapOption)
$(deriveJSON defaultOptions{ constructorTagModifier =
camelCaseStrToHyphenated . drop 8
} ''TopLevelDivision)
$(deriveJSON defaultOptions{ constructorTagModifier =
camelCaseStrToHyphenated
} ''ReferenceLocation)