{-# 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.Maybe (fromMaybe)
import Data.Data (Data)
import Data.Default
import Data.Char (toLower)
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.UTF8 (toStringLazy)
import Data.Aeson.TH (deriveJSON)
import Data.Aeson
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
$cshowsPrec :: Int -> ReaderOptions -> ShowS
showsPrec :: Int -> ReaderOptions -> ShowS
$cshow :: ReaderOptions -> String
show :: ReaderOptions -> String
$cshowList :: [ReaderOptions] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS ReaderOptions
readsPrec :: Int -> ReadS ReaderOptions
$creadList :: ReadS [ReaderOptions]
readList :: ReadS [ReaderOptions]
$creadPrec :: ReadPrec ReaderOptions
readPrec :: ReadPrec ReaderOptions
$creadListPrec :: ReadPrec [ReaderOptions]
readListPrec :: ReadPrec [ReaderOptions]
Read, Typeable ReaderOptions
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 -> Constr
ReaderOptions -> DataType
(forall b. Data b => b -> b) -> ReaderOptions -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReaderOptions -> c ReaderOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReaderOptions -> c ReaderOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReaderOptions
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReaderOptions
$ctoConstr :: ReaderOptions -> Constr
toConstr :: ReaderOptions -> Constr
$cdataTypeOf :: ReaderOptions -> DataType
dataTypeOf :: ReaderOptions -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReaderOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReaderOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReaderOptions)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReaderOptions)
$cgmapT :: (forall b. Data b => b -> b) -> ReaderOptions -> ReaderOptions
gmapT :: (forall b. Data b => b -> b) -> ReaderOptions -> ReaderOptions
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReaderOptions -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReaderOptions -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ReaderOptions -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReaderOptions -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReaderOptions -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m ReaderOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReaderOptions -> m 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
$cfrom :: forall x. ReaderOptions -> Rep ReaderOptions x
from :: forall x. ReaderOptions -> Rep ReaderOptions x
$cto :: forall x. Rep ReaderOptions x -> ReaderOptions
to :: forall x. Rep ReaderOptions x -> ReaderOptions
Generic)
instance HasSyntaxExtensions ReaderOptions where
getExtensions :: ReaderOptions -> Extensions
getExtensions ReaderOptions
opts = ReaderOptions -> Extensions
readerExtensions ReaderOptions
opts
instance Default ReaderOptions
where def :: ReaderOptions
def = 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
$c== :: EPUBVersion -> EPUBVersion -> Bool
== :: EPUBVersion -> EPUBVersion -> Bool
$c/= :: EPUBVersion -> EPUBVersion -> Bool
/= :: 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
$cshowsPrec :: Int -> EPUBVersion -> ShowS
showsPrec :: Int -> EPUBVersion -> ShowS
$cshow :: EPUBVersion -> String
show :: EPUBVersion -> String
$cshowList :: [EPUBVersion] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS EPUBVersion
readsPrec :: Int -> ReadS EPUBVersion
$creadList :: ReadS [EPUBVersion]
readList :: ReadS [EPUBVersion]
$creadPrec :: ReadPrec EPUBVersion
readPrec :: ReadPrec EPUBVersion
$creadListPrec :: ReadPrec [EPUBVersion]
readListPrec :: ReadPrec [EPUBVersion]
Read, Typeable EPUBVersion
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 -> Constr
EPUBVersion -> DataType
(forall b. Data b => b -> b) -> EPUBVersion -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EPUBVersion -> c EPUBVersion
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EPUBVersion -> c EPUBVersion
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EPUBVersion
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EPUBVersion
$ctoConstr :: EPUBVersion -> Constr
toConstr :: EPUBVersion -> Constr
$cdataTypeOf :: EPUBVersion -> DataType
dataTypeOf :: EPUBVersion -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EPUBVersion)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EPUBVersion)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EPUBVersion)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EPUBVersion)
$cgmapT :: (forall b. Data b => b -> b) -> EPUBVersion -> EPUBVersion
gmapT :: (forall b. Data b => b -> b) -> EPUBVersion -> EPUBVersion
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EPUBVersion -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EPUBVersion -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> EPUBVersion -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> EPUBVersion -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> EPUBVersion -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m EPUBVersion
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EPUBVersion -> m 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
$cfrom :: forall x. EPUBVersion -> Rep EPUBVersion x
from :: forall x. EPUBVersion -> Rep EPUBVersion x
$cto :: forall x. Rep EPUBVersion x -> EPUBVersion
to :: forall x. Rep EPUBVersion x -> EPUBVersion
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
$cshowsPrec :: Int -> HTMLMathMethod -> ShowS
showsPrec :: Int -> HTMLMathMethod -> ShowS
$cshow :: HTMLMathMethod -> String
show :: HTMLMathMethod -> String
$cshowList :: [HTMLMathMethod] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS HTMLMathMethod
readsPrec :: Int -> ReadS HTMLMathMethod
$creadList :: ReadS [HTMLMathMethod]
readList :: ReadS [HTMLMathMethod]
$creadPrec :: ReadPrec HTMLMathMethod
readPrec :: ReadPrec HTMLMathMethod
$creadListPrec :: ReadPrec [HTMLMathMethod]
readListPrec :: ReadPrec [HTMLMathMethod]
Read, HTMLMathMethod -> HTMLMathMethod -> Bool
(HTMLMathMethod -> HTMLMathMethod -> Bool)
-> (HTMLMathMethod -> HTMLMathMethod -> Bool) -> Eq HTMLMathMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HTMLMathMethod -> HTMLMathMethod -> Bool
== :: HTMLMathMethod -> HTMLMathMethod -> Bool
$c/= :: HTMLMathMethod -> HTMLMathMethod -> Bool
/= :: HTMLMathMethod -> HTMLMathMethod -> Bool
Eq, Typeable HTMLMathMethod
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 -> Constr
HTMLMathMethod -> DataType
(forall b. Data b => b -> b) -> HTMLMathMethod -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLMathMethod
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLMathMethod
$ctoConstr :: HTMLMathMethod -> Constr
toConstr :: HTMLMathMethod -> Constr
$cdataTypeOf :: HTMLMathMethod -> DataType
dataTypeOf :: HTMLMathMethod -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLMathMethod)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLMathMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLMathMethod)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLMathMethod)
$cgmapT :: (forall b. Data b => b -> b) -> HTMLMathMethod -> HTMLMathMethod
gmapT :: (forall b. Data b => b -> b) -> HTMLMathMethod -> HTMLMathMethod
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HTMLMathMethod -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> HTMLMathMethod -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HTMLMathMethod -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HTMLMathMethod -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m HTMLMathMethod
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLMathMethod -> m 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
$cfrom :: forall x. HTMLMathMethod -> Rep HTMLMathMethod x
from :: forall x. HTMLMathMethod -> Rep HTMLMathMethod x
$cto :: forall x. Rep HTMLMathMethod x -> HTMLMathMethod
to :: forall x. Rep HTMLMathMethod x -> HTMLMathMethod
Generic)
instance FromJSON HTMLMathMethod where
parseJSON :: Value -> Parser HTMLMathMethod
parseJSON Value
node =
(String
-> (Object -> Parser HTMLMathMethod)
-> Value
-> Parser HTMLMathMethod
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"HTMLMathMethod" ((Object -> Parser HTMLMathMethod)
-> Value -> Parser HTMLMathMethod)
-> (Object -> Parser HTMLMathMethod)
-> Value
-> Parser HTMLMathMethod
forall a b. (a -> b) -> a -> b
$ \Object
m -> do
Text
method <- Object
m Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"method"
Maybe Text
mburl <- Object
m Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"url"
case Text
method :: Text of
Text
"plain" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
PlainMath
Text
"webtex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
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 a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
GladTeX
Text
"mathml" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
MathML
Text
"mathjax" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
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 a. a -> Parser a
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 a. String -> Parser a
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) Value
node
Parser HTMLMathMethod
-> Parser HTMLMathMethod -> Parser HTMLMathMethod
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (case Value
node of
String Text
"plain" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
PlainMath
String Text
"webtex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
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
""
String Text
"gladtex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
GladTeX
String Text
"mathml" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return HTMLMathMethod
MathML
String Text
"mathjax" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
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
String Text
"katex" -> HTMLMathMethod -> Parser HTMLMathMethod
forall a. a -> Parser a
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
Value
_ -> String -> Parser HTMLMathMethod
forall a. String -> Parser a
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. Semigroup a => a -> a -> a
<>
ByteString -> String
toStringLazy (Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
node))
instance ToJSON HTMLMathMethod where
toJSON :: HTMLMathMethod -> Value
toJSON HTMLMathMethod
PlainMath = Text -> Value
String Text
"plain"
toJSON (WebTeX Text
"") = Text -> Value
String Text
"webtex"
toJSON (WebTeX Text
url) = [Pair] -> Value
object [Key
"method" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"webtex",
Key
"url" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
url]
toJSON HTMLMathMethod
GladTeX = Text -> Value
String Text
"gladtex"
toJSON HTMLMathMethod
MathML = Text -> Value
String Text
"mathml"
toJSON (MathJax Text
"") = Text -> Value
String Text
"mathjax"
toJSON (MathJax Text
url) = [Pair] -> Value
object [Key
"method" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"mathjax",
Key
"url" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
url]
toJSON (KaTeX Text
"") = Text -> Value
String Text
"katex"
toJSON (KaTeX Text
url) = [Pair] -> Value
object [Key
"method" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"katex",
Key
"url" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
url]
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
$cshowsPrec :: Int -> CiteMethod -> ShowS
showsPrec :: Int -> CiteMethod -> ShowS
$cshow :: CiteMethod -> String
show :: CiteMethod -> String
$cshowList :: [CiteMethod] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS CiteMethod
readsPrec :: Int -> ReadS CiteMethod
$creadList :: ReadS [CiteMethod]
readList :: ReadS [CiteMethod]
$creadPrec :: ReadPrec CiteMethod
readPrec :: ReadPrec CiteMethod
$creadListPrec :: ReadPrec [CiteMethod]
readListPrec :: ReadPrec [CiteMethod]
Read, CiteMethod -> CiteMethod -> Bool
(CiteMethod -> CiteMethod -> Bool)
-> (CiteMethod -> CiteMethod -> Bool) -> Eq CiteMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CiteMethod -> CiteMethod -> Bool
== :: CiteMethod -> CiteMethod -> Bool
$c/= :: CiteMethod -> CiteMethod -> Bool
/= :: CiteMethod -> CiteMethod -> Bool
Eq, Typeable CiteMethod
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 -> Constr
CiteMethod -> DataType
(forall b. Data b => b -> b) -> CiteMethod -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CiteMethod -> c CiteMethod
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CiteMethod -> c CiteMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CiteMethod
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CiteMethod
$ctoConstr :: CiteMethod -> Constr
toConstr :: CiteMethod -> Constr
$cdataTypeOf :: CiteMethod -> DataType
dataTypeOf :: CiteMethod -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CiteMethod)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CiteMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteMethod)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteMethod)
$cgmapT :: (forall b. Data b => b -> b) -> CiteMethod -> CiteMethod
gmapT :: (forall b. Data b => b -> b) -> CiteMethod -> CiteMethod
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CiteMethod -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CiteMethod -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CiteMethod -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CiteMethod -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CiteMethod -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m CiteMethod
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CiteMethod -> m 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
$cfrom :: forall x. CiteMethod -> Rep CiteMethod x
from :: forall x. CiteMethod -> Rep CiteMethod x
$cto :: forall x. Rep CiteMethod x -> CiteMethod
to :: forall x. Rep CiteMethod x -> CiteMethod
Generic)
instance FromJSON CiteMethod where
parseJSON :: Value -> Parser CiteMethod
parseJSON Value
v =
case Value
v of
String Text
"citeproc" -> CiteMethod -> Parser CiteMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return CiteMethod
Citeproc
String Text
"natbib" -> CiteMethod -> Parser CiteMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return CiteMethod
Natbib
String Text
"biblatex" -> CiteMethod -> Parser CiteMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return CiteMethod
Biblatex
Value
_ -> String -> Parser CiteMethod
forall a. String -> Parser a
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. Semigroup a => a -> a -> a
<>
ByteString -> String
toStringLazy (Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
v)
instance ToJSON CiteMethod where
toJSON :: CiteMethod -> Value
toJSON CiteMethod
Citeproc = Text -> Value
String Text
"citeproc"
toJSON CiteMethod
Natbib = Text -> Value
String Text
"natbib"
toJSON CiteMethod
Biblatex = Text -> Value
String Text
"biblatex"
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
$cshowsPrec :: Int -> ObfuscationMethod -> ShowS
showsPrec :: Int -> ObfuscationMethod -> ShowS
$cshow :: ObfuscationMethod -> String
show :: ObfuscationMethod -> String
$cshowList :: [ObfuscationMethod] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS ObfuscationMethod
readsPrec :: Int -> ReadS ObfuscationMethod
$creadList :: ReadS [ObfuscationMethod]
readList :: ReadS [ObfuscationMethod]
$creadPrec :: ReadPrec ObfuscationMethod
readPrec :: ReadPrec ObfuscationMethod
$creadListPrec :: ReadPrec [ObfuscationMethod]
readListPrec :: ReadPrec [ObfuscationMethod]
Read, ObfuscationMethod -> ObfuscationMethod -> Bool
(ObfuscationMethod -> ObfuscationMethod -> Bool)
-> (ObfuscationMethod -> ObfuscationMethod -> Bool)
-> Eq ObfuscationMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObfuscationMethod -> ObfuscationMethod -> Bool
== :: ObfuscationMethod -> ObfuscationMethod -> Bool
$c/= :: ObfuscationMethod -> ObfuscationMethod -> Bool
/= :: ObfuscationMethod -> ObfuscationMethod -> Bool
Eq, Typeable ObfuscationMethod
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 -> Constr
ObfuscationMethod -> DataType
(forall b. Data b => b -> b)
-> ObfuscationMethod -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ObfuscationMethod -> c ObfuscationMethod
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ObfuscationMethod -> c ObfuscationMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ObfuscationMethod
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ObfuscationMethod
$ctoConstr :: ObfuscationMethod -> Constr
toConstr :: ObfuscationMethod -> Constr
$cdataTypeOf :: ObfuscationMethod -> DataType
dataTypeOf :: ObfuscationMethod -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ObfuscationMethod)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ObfuscationMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ObfuscationMethod)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ObfuscationMethod)
$cgmapT :: (forall b. Data b => b -> b)
-> ObfuscationMethod -> ObfuscationMethod
gmapT :: (forall b. Data b => b -> b)
-> ObfuscationMethod -> ObfuscationMethod
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ObfuscationMethod -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ObfuscationMethod -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ObfuscationMethod -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ObfuscationMethod -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m ObfuscationMethod
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ObfuscationMethod -> m 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
$cfrom :: forall x. ObfuscationMethod -> Rep ObfuscationMethod x
from :: forall x. ObfuscationMethod -> Rep ObfuscationMethod x
$cto :: forall x. Rep ObfuscationMethod x -> ObfuscationMethod
to :: forall x. Rep ObfuscationMethod x -> ObfuscationMethod
Generic)
instance FromJSON ObfuscationMethod where
parseJSON :: Value -> Parser ObfuscationMethod
parseJSON Value
v =
case Value
v of
String Text
"none" -> ObfuscationMethod -> Parser ObfuscationMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ObfuscationMethod
NoObfuscation
String Text
"references" -> ObfuscationMethod -> Parser ObfuscationMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ObfuscationMethod
ReferenceObfuscation
String Text
"javascript" -> ObfuscationMethod -> Parser ObfuscationMethod
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ObfuscationMethod
JavascriptObfuscation
Value
_ -> String -> Parser ObfuscationMethod
forall a. String -> Parser a
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]
++ ByteString -> String
toStringLazy (Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
v)
instance ToJSON ObfuscationMethod where
toJSON :: ObfuscationMethod -> Value
toJSON ObfuscationMethod
NoObfuscation = Text -> Value
String Text
"none"
toJSON ObfuscationMethod
ReferenceObfuscation = Text -> Value
String Text
"references"
toJSON ObfuscationMethod
JavascriptObfuscation = Text -> Value
String Text
"javascript"
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
$cshowsPrec :: Int -> HTMLSlideVariant -> ShowS
showsPrec :: Int -> HTMLSlideVariant -> ShowS
$cshow :: HTMLSlideVariant -> String
show :: HTMLSlideVariant -> String
$cshowList :: [HTMLSlideVariant] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS HTMLSlideVariant
readsPrec :: Int -> ReadS HTMLSlideVariant
$creadList :: ReadS [HTMLSlideVariant]
readList :: ReadS [HTMLSlideVariant]
$creadPrec :: ReadPrec HTMLSlideVariant
readPrec :: ReadPrec HTMLSlideVariant
$creadListPrec :: ReadPrec [HTMLSlideVariant]
readListPrec :: ReadPrec [HTMLSlideVariant]
Read, HTMLSlideVariant -> HTMLSlideVariant -> Bool
(HTMLSlideVariant -> HTMLSlideVariant -> Bool)
-> (HTMLSlideVariant -> HTMLSlideVariant -> Bool)
-> Eq HTMLSlideVariant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
== :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
$c/= :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
/= :: HTMLSlideVariant -> HTMLSlideVariant -> Bool
Eq, Typeable HTMLSlideVariant
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 -> Constr
HTMLSlideVariant -> DataType
(forall b. Data b => b -> b)
-> HTMLSlideVariant -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant
$ctoConstr :: HTMLSlideVariant -> Constr
toConstr :: HTMLSlideVariant -> Constr
$cdataTypeOf :: HTMLSlideVariant -> DataType
dataTypeOf :: HTMLSlideVariant -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLSlideVariant)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HTMLSlideVariant)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLSlideVariant)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HTMLSlideVariant)
$cgmapT :: (forall b. Data b => b -> b)
-> HTMLSlideVariant -> HTMLSlideVariant
gmapT :: (forall b. Data b => b -> b)
-> HTMLSlideVariant -> HTMLSlideVariant
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HTMLSlideVariant -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> HTMLSlideVariant -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HTMLSlideVariant -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HTMLSlideVariant -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m HTMLSlideVariant
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HTMLSlideVariant -> m 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
$cfrom :: forall x. HTMLSlideVariant -> Rep HTMLSlideVariant x
from :: forall x. HTMLSlideVariant -> Rep HTMLSlideVariant x
$cto :: forall x. Rep HTMLSlideVariant x -> HTMLSlideVariant
to :: forall x. Rep HTMLSlideVariant x -> HTMLSlideVariant
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
$cshowsPrec :: Int -> TrackChanges -> ShowS
showsPrec :: Int -> TrackChanges -> ShowS
$cshow :: TrackChanges -> String
show :: TrackChanges -> String
$cshowList :: [TrackChanges] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS TrackChanges
readsPrec :: Int -> ReadS TrackChanges
$creadList :: ReadS [TrackChanges]
readList :: ReadS [TrackChanges]
$creadPrec :: ReadPrec TrackChanges
readPrec :: ReadPrec TrackChanges
$creadListPrec :: ReadPrec [TrackChanges]
readListPrec :: ReadPrec [TrackChanges]
Read, TrackChanges -> TrackChanges -> Bool
(TrackChanges -> TrackChanges -> Bool)
-> (TrackChanges -> TrackChanges -> Bool) -> Eq TrackChanges
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TrackChanges -> TrackChanges -> Bool
== :: TrackChanges -> TrackChanges -> Bool
$c/= :: TrackChanges -> TrackChanges -> Bool
/= :: TrackChanges -> TrackChanges -> Bool
Eq, Typeable TrackChanges
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 -> Constr
TrackChanges -> DataType
(forall b. Data b => b -> b) -> TrackChanges -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TrackChanges -> c TrackChanges
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TrackChanges -> c TrackChanges
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TrackChanges
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TrackChanges
$ctoConstr :: TrackChanges -> Constr
toConstr :: TrackChanges -> Constr
$cdataTypeOf :: TrackChanges -> DataType
dataTypeOf :: TrackChanges -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TrackChanges)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TrackChanges)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TrackChanges)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TrackChanges)
$cgmapT :: (forall b. Data b => b -> b) -> TrackChanges -> TrackChanges
gmapT :: (forall b. Data b => b -> b) -> TrackChanges -> TrackChanges
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TrackChanges -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TrackChanges -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TrackChanges -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TrackChanges -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TrackChanges -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m TrackChanges
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TrackChanges -> m 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
$cfrom :: forall x. TrackChanges -> Rep TrackChanges x
from :: forall x. TrackChanges -> Rep TrackChanges x
$cto :: forall x. Rep TrackChanges x -> TrackChanges
to :: forall x. Rep TrackChanges x -> TrackChanges
Generic)
instance FromJSON TrackChanges where
parseJSON :: Value -> Parser TrackChanges
parseJSON Value
v =
case Value
v of
String Text
"accept" -> TrackChanges -> Parser TrackChanges
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
AcceptChanges
String Text
"reject" -> TrackChanges -> Parser TrackChanges
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
RejectChanges
String Text
"all" -> TrackChanges -> Parser TrackChanges
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
AllChanges
String Text
"accept-changes" -> TrackChanges -> Parser TrackChanges
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
AcceptChanges
String Text
"reject-changes" -> TrackChanges -> Parser TrackChanges
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
RejectChanges
String Text
"all-changes" -> TrackChanges -> Parser TrackChanges
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TrackChanges
AllChanges
Value
_ -> String -> Parser TrackChanges
forall a. String -> Parser a
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. Semigroup a => a -> a -> a
<> ByteString -> String
toStringLazy (Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
v)
instance ToJSON TrackChanges where
toJSON :: TrackChanges -> Value
toJSON TrackChanges
AcceptChanges = Text -> Value
String Text
"accept-changes"
toJSON TrackChanges
RejectChanges = Text -> Value
String Text
"reject-changes"
toJSON TrackChanges
AllChanges = Text -> Value
String Text
"all-changes"
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
$cshowsPrec :: Int -> WrapOption -> ShowS
showsPrec :: Int -> WrapOption -> ShowS
$cshow :: WrapOption -> String
show :: WrapOption -> String
$cshowList :: [WrapOption] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS WrapOption
readsPrec :: Int -> ReadS WrapOption
$creadList :: ReadS [WrapOption]
readList :: ReadS [WrapOption]
$creadPrec :: ReadPrec WrapOption
readPrec :: ReadPrec WrapOption
$creadListPrec :: ReadPrec [WrapOption]
readListPrec :: ReadPrec [WrapOption]
Read, WrapOption -> WrapOption -> Bool
(WrapOption -> WrapOption -> Bool)
-> (WrapOption -> WrapOption -> Bool) -> Eq WrapOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WrapOption -> WrapOption -> Bool
== :: WrapOption -> WrapOption -> Bool
$c/= :: WrapOption -> WrapOption -> Bool
/= :: WrapOption -> WrapOption -> Bool
Eq, Typeable WrapOption
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 -> Constr
WrapOption -> DataType
(forall b. Data b => b -> b) -> WrapOption -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapOption -> c WrapOption
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapOption -> c WrapOption
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WrapOption
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WrapOption
$ctoConstr :: WrapOption -> Constr
toConstr :: WrapOption -> Constr
$cdataTypeOf :: WrapOption -> DataType
dataTypeOf :: WrapOption -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WrapOption)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WrapOption)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WrapOption)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WrapOption)
$cgmapT :: (forall b. Data b => b -> b) -> WrapOption -> WrapOption
gmapT :: (forall b. Data b => b -> b) -> WrapOption -> WrapOption
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapOption -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WrapOption -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> WrapOption -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WrapOption -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WrapOption -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WrapOption -> m WrapOption
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapOption -> m 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
$cfrom :: forall x. WrapOption -> Rep WrapOption x
from :: forall x. WrapOption -> Rep WrapOption x
$cto :: forall x. Rep WrapOption x -> WrapOption
to :: forall x. Rep WrapOption x -> WrapOption
Generic)
instance FromJSON WrapOption where
parseJSON :: Value -> Parser WrapOption
parseJSON Value
v =
case Value
v of
String Text
"auto" -> WrapOption -> Parser WrapOption
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapAuto
String Text
"wrap-auto" -> WrapOption -> Parser WrapOption
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapAuto
String Text
"none" -> WrapOption -> Parser WrapOption
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapNone
String Text
"wrap-none" -> WrapOption -> Parser WrapOption
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapNone
String Text
"preserve" -> WrapOption -> Parser WrapOption
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapPreserve
String Text
"wrap-preserve" -> WrapOption -> Parser WrapOption
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return WrapOption
WrapPreserve
Value
_ -> String -> Parser WrapOption
forall a. String -> Parser a
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. Semigroup a => a -> a -> a
<> ByteString -> String
toStringLazy (Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
v)
instance ToJSON WrapOption where
toJSON :: WrapOption -> Value
toJSON WrapOption
WrapAuto = Value
"wrap-auto"
toJSON WrapOption
WrapNone = Value
"wrap-none"
toJSON WrapOption
WrapPreserve = Value
"wrap-preserve"
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
$cshowsPrec :: Int -> TopLevelDivision -> ShowS
showsPrec :: Int -> TopLevelDivision -> ShowS
$cshow :: TopLevelDivision -> String
show :: TopLevelDivision -> String
$cshowList :: [TopLevelDivision] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS TopLevelDivision
readsPrec :: Int -> ReadS TopLevelDivision
$creadList :: ReadS [TopLevelDivision]
readList :: ReadS [TopLevelDivision]
$creadPrec :: ReadPrec TopLevelDivision
readPrec :: ReadPrec TopLevelDivision
$creadListPrec :: ReadPrec [TopLevelDivision]
readListPrec :: ReadPrec [TopLevelDivision]
Read, TopLevelDivision -> TopLevelDivision -> Bool
(TopLevelDivision -> TopLevelDivision -> Bool)
-> (TopLevelDivision -> TopLevelDivision -> Bool)
-> Eq TopLevelDivision
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TopLevelDivision -> TopLevelDivision -> Bool
== :: TopLevelDivision -> TopLevelDivision -> Bool
$c/= :: TopLevelDivision -> TopLevelDivision -> Bool
/= :: TopLevelDivision -> TopLevelDivision -> Bool
Eq, Typeable TopLevelDivision
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 -> Constr
TopLevelDivision -> DataType
(forall b. Data b => b -> b)
-> TopLevelDivision -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelDivision
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelDivision
$ctoConstr :: TopLevelDivision -> Constr
toConstr :: TopLevelDivision -> Constr
$cdataTypeOf :: TopLevelDivision -> DataType
dataTypeOf :: TopLevelDivision -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelDivision)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelDivision)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelDivision)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelDivision)
$cgmapT :: (forall b. Data b => b -> b)
-> TopLevelDivision -> TopLevelDivision
gmapT :: (forall b. Data b => b -> b)
-> TopLevelDivision -> TopLevelDivision
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TopLevelDivision -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TopLevelDivision -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TopLevelDivision -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TopLevelDivision -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m TopLevelDivision
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TopLevelDivision -> m 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
$cfrom :: forall x. TopLevelDivision -> Rep TopLevelDivision x
from :: forall x. TopLevelDivision -> Rep TopLevelDivision x
$cto :: forall x. Rep TopLevelDivision x -> TopLevelDivision
to :: forall x. Rep TopLevelDivision x -> TopLevelDivision
Generic)
instance FromJSON TopLevelDivision where
parseJSON :: Value -> Parser TopLevelDivision
parseJSON Value
v =
case Value
v of
String Text
"part" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelPart
String Text
"top-level-part" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelPart
String Text
"chapter" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelChapter
String Text
"top-level-chapter" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelChapter
String Text
"section" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelSection
String Text
"top-level-section" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelSection
String Text
"default" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelDefault
String Text
"top-level-default" -> TopLevelDivision -> Parser TopLevelDivision
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TopLevelDivision
TopLevelDefault
Value
_ -> String -> Parser TopLevelDivision
forall a. String -> Parser a
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. Semigroup a => a -> a -> a
<> ByteString -> String
toStringLazy (Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
v)
instance ToJSON TopLevelDivision where
toJSON :: TopLevelDivision -> Value
toJSON TopLevelDivision
TopLevelPart = Value
"top-level-part"
toJSON TopLevelDivision
TopLevelChapter = Value
"top-level-chapter"
toJSON TopLevelDivision
TopLevelSection = Value
"top-level-section"
toJSON TopLevelDivision
TopLevelDefault = Value
"top-level-default"
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
$cshowsPrec :: Int -> ReferenceLocation -> ShowS
showsPrec :: Int -> ReferenceLocation -> ShowS
$cshow :: ReferenceLocation -> String
show :: ReferenceLocation -> String
$cshowList :: [ReferenceLocation] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS ReferenceLocation
readsPrec :: Int -> ReadS ReferenceLocation
$creadList :: ReadS [ReferenceLocation]
readList :: ReadS [ReferenceLocation]
$creadPrec :: ReadPrec ReferenceLocation
readPrec :: ReadPrec ReferenceLocation
$creadListPrec :: ReadPrec [ReferenceLocation]
readListPrec :: ReadPrec [ReferenceLocation]
Read, ReferenceLocation -> ReferenceLocation -> Bool
(ReferenceLocation -> ReferenceLocation -> Bool)
-> (ReferenceLocation -> ReferenceLocation -> Bool)
-> Eq ReferenceLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReferenceLocation -> ReferenceLocation -> Bool
== :: ReferenceLocation -> ReferenceLocation -> Bool
$c/= :: ReferenceLocation -> ReferenceLocation -> Bool
/= :: ReferenceLocation -> ReferenceLocation -> Bool
Eq, Typeable ReferenceLocation
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 -> Constr
ReferenceLocation -> DataType
(forall b. Data b => b -> b)
-> ReferenceLocation -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceLocation -> c ReferenceLocation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceLocation -> c ReferenceLocation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceLocation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceLocation
$ctoConstr :: ReferenceLocation -> Constr
toConstr :: ReferenceLocation -> Constr
$cdataTypeOf :: ReferenceLocation -> DataType
dataTypeOf :: ReferenceLocation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceLocation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceLocation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceLocation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceLocation)
$cgmapT :: (forall b. Data b => b -> b)
-> ReferenceLocation -> ReferenceLocation
gmapT :: (forall b. Data b => b -> b)
-> ReferenceLocation -> ReferenceLocation
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReferenceLocation -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ReferenceLocation -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ReferenceLocation -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ReferenceLocation -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m ReferenceLocation
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReferenceLocation -> m 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
$cfrom :: forall x. ReferenceLocation -> Rep ReferenceLocation x
from :: forall x. ReferenceLocation -> Rep ReferenceLocation x
$cto :: forall x. Rep ReferenceLocation x -> ReferenceLocation
to :: forall x. Rep ReferenceLocation x -> ReferenceLocation
Generic)
instance FromJSON ReferenceLocation where
parseJSON :: Value -> Parser ReferenceLocation
parseJSON Value
v =
case Value
v of
String Text
"block" -> ReferenceLocation -> Parser ReferenceLocation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfBlock
String Text
"end-of-block" -> ReferenceLocation -> Parser ReferenceLocation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfBlock
String Text
"section" -> ReferenceLocation -> Parser ReferenceLocation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfSection
String Text
"end-of-section" -> ReferenceLocation -> Parser ReferenceLocation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfSection
String Text
"document" -> ReferenceLocation -> Parser ReferenceLocation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfDocument
String Text
"end-of-document" -> ReferenceLocation -> Parser ReferenceLocation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReferenceLocation
EndOfDocument
Value
_ -> String -> Parser ReferenceLocation
forall a. String -> Parser a
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. Semigroup a => a -> a -> a
<> ByteString -> String
toStringLazy (Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
v)
instance ToJSON ReferenceLocation where
toJSON :: ReferenceLocation -> Value
toJSON ReferenceLocation
EndOfBlock = Value
"end-of-block"
toJSON ReferenceLocation
EndOfSection = Value
"end-of-section"
toJSON ReferenceLocation
EndOfDocument = Value
"end-of-document"
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 -> Bool
writerListTables :: Bool
, WriterOptions -> Text
writerEpubSubdirectory :: Text
, WriterOptions -> Maybe Text
writerEpubMetadata :: Maybe Text
, WriterOptions -> [String]
writerEpubFonts :: [FilePath]
, WriterOptions -> Bool
writerEpubTitlePage :: Bool
, WriterOptions -> Int
writerSplitLevel :: 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
$cshowsPrec :: Int -> WriterOptions -> ShowS
showsPrec :: Int -> WriterOptions -> ShowS
$cshow :: WriterOptions -> String
show :: WriterOptions -> String
$cshowList :: [WriterOptions] -> ShowS
showList :: [WriterOptions] -> ShowS
Show, Typeable WriterOptions
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 -> Constr
WriterOptions -> DataType
(forall b. Data b => b -> b) -> WriterOptions -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WriterOptions -> c WriterOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WriterOptions -> c WriterOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WriterOptions
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WriterOptions
$ctoConstr :: WriterOptions -> Constr
toConstr :: WriterOptions -> Constr
$cdataTypeOf :: WriterOptions -> DataType
dataTypeOf :: WriterOptions -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WriterOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WriterOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WriterOptions)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WriterOptions)
$cgmapT :: (forall b. Data b => b -> b) -> WriterOptions -> WriterOptions
gmapT :: (forall b. Data b => b -> b) -> WriterOptions -> WriterOptions
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WriterOptions -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WriterOptions -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> WriterOptions -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WriterOptions -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WriterOptions -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WriterOptions -> m 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
$cfrom :: forall x. WriterOptions -> Rep WriterOptions x
from :: forall x. WriterOptions -> Rep WriterOptions x
$cto :: forall x. Rep WriterOptions x -> WriterOptions
to :: forall x. Rep WriterOptions x -> WriterOptions
Generic)
instance Default WriterOptions where
def :: WriterOptions
def = 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
, writerListTables :: Bool
writerListTables = Bool
False
, writerEpubSubdirectory :: Text
writerEpubSubdirectory = Text
"EPUB"
, writerEpubMetadata :: Maybe Text
writerEpubMetadata = Maybe Text
forall a. Maybe a
Nothing
, writerEpubFonts :: [String]
writerEpubFonts = []
, writerEpubTitlePage :: Bool
writerEpubTitlePage = Bool
True
, writerSplitLevel :: Int
writerSplitLevel = 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 :: forall a. HasSyntaxExtensions a => 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://cdn.jsdelivr.net/npm/katex@0.15.1/dist/"
$(deriveJSON defaultOptions{ fieldLabelModifier =
camelTo2 '-' . drop 6 }
''ReaderOptions)
$(deriveJSON defaultOptions{ constructorTagModifier = map toLower }
''HTMLSlideVariant)