{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE CPP                 #-}
{-# LANGUAGE DeriveGeneric       #-}
{-# LANGUAGE TemplateHaskell     #-}
{-# LANGUAGE FlexibleInstances   #-}
{-# LANGUAGE FlexibleContexts    #-}
module Text.Pandoc.App.Opt (
            Opt(..)
          , OptInfo(..)
          , LineEnding (..)
          , IpynbOutput (..)
          , DefaultsState (..)
          , defaultOpts
          , applyDefaults
          , fullDefaultsPath
          ) where
import Control.Monad.Except (throwError)
import Control.Monad.Trans (MonadIO, liftIO)
import Control.Monad ((>=>), foldM)
import Control.Monad.State.Strict (StateT, modify, gets)
import System.FilePath ( addExtension, (</>), takeExtension, takeDirectory )
import System.Directory ( canonicalizePath )
import Data.Char (toLower)
import Data.Maybe (fromMaybe)
import GHC.Generics hiding (Meta)
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Logging (Verbosity (WARNING), LogMessage(..))
import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
                            TrackChanges (AcceptChanges),
                            WrapOption (WrapAuto), HTMLMathMethod (PlainMath),
                            ReferenceLocation (EndOfDocument),
                            ObfuscationMethod (NoObfuscation),
                            CiteMethod (Citeproc))
import Text.Pandoc.Class (readFileStrict, fileExists, setVerbosity, report,
                          PandocMonad(lookupEnv), getUserDataDir)
import Text.Pandoc.Error (PandocError (PandocParseError, PandocSomeError))
import Data.Containers.ListUtils (nubOrd)
import Text.Pandoc.Data (defaultUserDataDir)
import qualified Text.Pandoc.Parsing as P
import Text.Pandoc.Readers.Metadata (yamlMap)
import Text.Pandoc.Class.PandocPure
import Text.DocTemplates (Context(..))
import Data.Text (Text, unpack)
import Data.Default (def)
import qualified Data.Text as T
import qualified Data.Map as M
import qualified Data.ByteString.Char8 as B8
import Text.Pandoc.Definition (Meta(..), MetaValue(..))
import Data.Aeson (defaultOptions, Options(..), Result(..),
                   genericToJSON, fromJSON, camelTo2)
import Data.Aeson.TH (deriveJSON)
import Control.Applicative ((<|>))
import Data.Yaml
data LineEnding = LF | CRLF | Native deriving (Int -> LineEnding -> ShowS
[LineEnding] -> ShowS
LineEnding -> FilePath
(Int -> LineEnding -> ShowS)
-> (LineEnding -> FilePath)
-> ([LineEnding] -> ShowS)
-> Show LineEnding
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LineEnding -> ShowS
showsPrec :: Int -> LineEnding -> ShowS
$cshow :: LineEnding -> FilePath
show :: LineEnding -> FilePath
$cshowList :: [LineEnding] -> ShowS
showList :: [LineEnding] -> ShowS
Show, (forall x. LineEnding -> Rep LineEnding x)
-> (forall x. Rep LineEnding x -> LineEnding) -> Generic LineEnding
forall x. Rep LineEnding x -> LineEnding
forall x. LineEnding -> Rep LineEnding x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LineEnding -> Rep LineEnding x
from :: forall x. LineEnding -> Rep LineEnding x
$cto :: forall x. Rep LineEnding x -> LineEnding
to :: forall x. Rep LineEnding x -> LineEnding
Generic)
$(deriveJSON
   defaultOptions{ constructorTagModifier = map toLower } ''LineEnding)
data IpynbOutput =
    IpynbOutputAll
  | IpynbOutputNone
  | IpynbOutputBest
  deriving (Int -> IpynbOutput -> ShowS
[IpynbOutput] -> ShowS
IpynbOutput -> FilePath
(Int -> IpynbOutput -> ShowS)
-> (IpynbOutput -> FilePath)
-> ([IpynbOutput] -> ShowS)
-> Show IpynbOutput
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IpynbOutput -> ShowS
showsPrec :: Int -> IpynbOutput -> ShowS
$cshow :: IpynbOutput -> FilePath
show :: IpynbOutput -> FilePath
$cshowList :: [IpynbOutput] -> ShowS
showList :: [IpynbOutput] -> ShowS
Show, (forall x. IpynbOutput -> Rep IpynbOutput x)
-> (forall x. Rep IpynbOutput x -> IpynbOutput)
-> Generic IpynbOutput
forall x. Rep IpynbOutput x -> IpynbOutput
forall x. IpynbOutput -> Rep IpynbOutput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IpynbOutput -> Rep IpynbOutput x
from :: forall x. IpynbOutput -> Rep IpynbOutput x
$cto :: forall x. Rep IpynbOutput x -> IpynbOutput
to :: forall x. Rep IpynbOutput x -> IpynbOutput
Generic)
$(deriveJSON
   defaultOptions{ fieldLabelModifier = map toLower . drop 11 } ''IpynbOutput)
data OptInfo =
     BashCompletion
   | ListInputFormats
   | ListOutputFormats
   | ListExtensions (Maybe Text)
   | ListHighlightLanguages
   | ListHighlightStyles
   | PrintDefaultTemplate (Maybe FilePath) Text
   | PrintDefaultDataFile (Maybe FilePath) Text
   | PrintHighlightStyle (Maybe FilePath) Text
   | VersionInfo
   | Help
   | OptError PandocError
   deriving (Int -> OptInfo -> ShowS
[OptInfo] -> ShowS
OptInfo -> FilePath
(Int -> OptInfo -> ShowS)
-> (OptInfo -> FilePath) -> ([OptInfo] -> ShowS) -> Show OptInfo
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OptInfo -> ShowS
showsPrec :: Int -> OptInfo -> ShowS
$cshow :: OptInfo -> FilePath
show :: OptInfo -> FilePath
$cshowList :: [OptInfo] -> ShowS
showList :: [OptInfo] -> ShowS
Show, (forall x. OptInfo -> Rep OptInfo x)
-> (forall x. Rep OptInfo x -> OptInfo) -> Generic OptInfo
forall x. Rep OptInfo x -> OptInfo
forall x. OptInfo -> Rep OptInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OptInfo -> Rep OptInfo x
from :: forall x. OptInfo -> Rep OptInfo x
$cto :: forall x. Rep OptInfo x -> OptInfo
to :: forall x. Rep OptInfo x -> OptInfo
Generic)
data Opt = Opt
    { Opt -> Int
optTabStop               :: Int     
    , Opt -> Bool
optPreserveTabs          :: Bool    
    , Opt -> Bool
optStandalone            :: Bool    
    , Opt -> Maybe Text
optFrom                  :: Maybe Text  
    , Opt -> Maybe Text
optTo                    :: Maybe Text  
    , Opt -> Bool
optTableOfContents       :: Bool    
    , Opt -> Int
optShiftHeadingLevelBy   :: Int     
    , Opt -> Maybe FilePath
optTemplate              :: Maybe FilePath  
    , Opt -> Context Text
optVariables             :: Context Text    
    , Opt -> Meta
optMetadata              :: Meta 
    , Opt -> [FilePath]
optMetadataFiles         :: [FilePath]  
    , Opt -> Maybe FilePath
optOutputFile            :: Maybe FilePath  
    , Opt -> Maybe [FilePath]
optInputFiles            :: Maybe [FilePath] 
    , Opt -> Bool
optNumberSections        :: Bool    
    , Opt -> [Int]
optNumberOffset          :: [Int]   
    , Opt -> Bool
optSectionDivs           :: Bool    
    , Opt -> Bool
optIncremental           :: Bool    
    , Opt -> Bool
optSelfContained         :: Bool    
    , Opt -> Bool
optEmbedResources        :: Bool    
    , Opt -> Bool
optHtmlQTags             :: Bool    
    , Opt -> Maybe Text
optHighlightStyle        :: Maybe Text 
    , Opt -> [FilePath]
optSyntaxDefinitions     :: [FilePath]  
    , Opt -> TopLevelDivision
optTopLevelDivision      :: TopLevelDivision 
    , Opt -> HTMLMathMethod
optHTMLMathMethod        :: HTMLMathMethod 
    , Opt -> Maybe FilePath
optAbbreviations         :: Maybe FilePath 
    , Opt -> Maybe FilePath
optReferenceDoc          :: Maybe FilePath 
    , Opt -> Int
optSplitLevel            :: Int     
    , Opt -> Maybe Text
optChunkTemplate         :: Maybe Text 
    , Opt -> FilePath
optEpubSubdirectory      :: String 
    , Opt -> Maybe FilePath
optEpubMetadata          :: Maybe FilePath   
    , Opt -> [FilePath]
optEpubFonts             :: [FilePath] 
    , Opt -> Maybe FilePath
optEpubCoverImage        :: Maybe FilePath 
    , Opt -> Bool
optEpubTitlePage         :: Bool 
    , Opt -> Int
optTOCDepth              :: Int     
    , Opt -> Bool
optDumpArgs              :: Bool    
    , Opt -> Bool
optIgnoreArgs            :: Bool    
    , Opt -> Verbosity
optVerbosity             :: Verbosity  
    , Opt -> Bool
optTrace                 :: Bool  
    , Opt -> Maybe FilePath
optLogFile               :: Maybe FilePath 
    , Opt -> Bool
optFailIfWarnings        :: Bool    
    , Opt -> Bool
optReferenceLinks        :: Bool    
    , Opt -> ReferenceLocation
optReferenceLocation     :: ReferenceLocation 
    , Opt -> Int
optDpi                   :: Int     
    , Opt -> WrapOption
optWrap                  :: WrapOption  
    , Opt -> Int
optColumns               :: Int     
    , Opt -> [Filter]
optFilters               :: [Filter] 
    , Opt -> ObfuscationMethod
optEmailObfuscation      :: ObfuscationMethod
    , Opt -> Text
optIdentifierPrefix      :: Text
    , Opt -> [Text]
optIndentedCodeClasses   :: [Text] 
    , Opt -> Maybe FilePath
optDataDir               :: Maybe FilePath
    , Opt -> CiteMethod
optCiteMethod            :: CiteMethod 
    , Opt -> Bool
optListings              :: Bool       
    , Opt -> Maybe FilePath
optPdfEngine             :: Maybe String 
    , Opt -> [FilePath]
optPdfEngineOpts         :: [String]   
    , Opt -> Maybe Int
optSlideLevel            :: Maybe Int  
    ,          :: Bool       
    , Opt -> Bool
optListTables            :: Bool       
    , Opt -> Bool
optAscii                 :: Bool       
    , Opt -> Text
optDefaultImageExtension :: Text       
    ,           :: Maybe FilePath 
    , Opt -> TrackChanges
optTrackChanges          :: TrackChanges 
    , Opt -> Bool
optFileScope             :: Bool         
    , Opt -> Maybe Text
optTitlePrefix           :: Maybe Text     
    , Opt -> [FilePath]
optCss                   :: [FilePath]       
    , Opt -> IpynbOutput
optIpynbOutput           :: IpynbOutput      
    , Opt -> [FilePath]
optIncludeBeforeBody     :: [FilePath]       
    , Opt -> [FilePath]
optIncludeAfterBody      :: [FilePath]       
    ,        :: [FilePath]       
    , Opt -> [FilePath]
optResourcePath          :: [FilePath] 
    ,         :: [(Text, Text)] 
    , Opt -> Bool
optNoCheckCertificate    :: Bool       
    , Opt -> LineEnding
optEol                   :: LineEnding 
    ,          :: Bool       
    , Opt -> Maybe FilePath
optCSL                   :: Maybe FilePath 
    , Opt -> [FilePath]
optBibliography          :: [FilePath]  
    , Opt -> Maybe FilePath
optCitationAbbreviations :: Maybe FilePath 
    , Opt -> Bool
optSandbox               :: Bool
    } deriving ((forall x. Opt -> Rep Opt x)
-> (forall x. Rep Opt x -> Opt) -> Generic Opt
forall x. Rep Opt x -> Opt
forall x. Opt -> Rep Opt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Opt -> Rep Opt x
from :: forall x. Opt -> Rep Opt x
$cto :: forall x. Rep Opt x -> Opt
to :: forall x. Rep Opt x -> Opt
Generic, Int -> Opt -> ShowS
[Opt] -> ShowS
Opt -> FilePath
(Int -> Opt -> ShowS)
-> (Opt -> FilePath) -> ([Opt] -> ShowS) -> Show Opt
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Opt -> ShowS
showsPrec :: Int -> Opt -> ShowS
$cshow :: Opt -> FilePath
show :: Opt -> FilePath
$cshowList :: [Opt] -> ShowS
showList :: [Opt] -> ShowS
Show)
instance FromJSON Opt where
   parseJSON :: Value -> Parser Opt
parseJSON = FilePath -> (Object -> Parser Opt) -> Value -> Parser Opt
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject FilePath
"Opt" ((Object -> Parser Opt) -> Value -> Parser Opt)
-> (Object -> Parser Opt) -> Value -> Parser Opt
forall a b. (a -> b) -> a -> b
$ \Object
o ->
     Int
-> Bool
-> Bool
-> Maybe Text
-> Maybe Text
-> Bool
-> Int
-> Maybe FilePath
-> Context Text
-> Meta
-> [FilePath]
-> Maybe FilePath
-> Maybe [FilePath]
-> Bool
-> [Int]
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> [FilePath]
-> TopLevelDivision
-> HTMLMathMethod
-> Maybe FilePath
-> Maybe FilePath
-> Int
-> Maybe Text
-> FilePath
-> Maybe FilePath
-> [FilePath]
-> Maybe FilePath
-> Bool
-> Int
-> Bool
-> Bool
-> Verbosity
-> Bool
-> Maybe FilePath
-> Bool
-> Bool
-> ReferenceLocation
-> Int
-> WrapOption
-> Int
-> [Filter]
-> ObfuscationMethod
-> Text
-> [Text]
-> Maybe FilePath
-> CiteMethod
-> Bool
-> Maybe FilePath
-> [FilePath]
-> Maybe Int
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> TrackChanges
-> Bool
-> Maybe Text
-> [FilePath]
-> IpynbOutput
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> [(Text, Text)]
-> Bool
-> LineEnding
-> Bool
-> Maybe FilePath
-> [FilePath]
-> Maybe FilePath
-> Bool
-> Opt
Opt
       (Int
 -> Bool
 -> Bool
 -> Maybe Text
 -> Maybe Text
 -> Bool
 -> Int
 -> Maybe FilePath
 -> Context Text
 -> Meta
 -> [FilePath]
 -> Maybe FilePath
 -> Maybe [FilePath]
 -> Bool
 -> [Int]
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Maybe Text
 -> [FilePath]
 -> TopLevelDivision
 -> HTMLMathMethod
 -> Maybe FilePath
 -> Maybe FilePath
 -> Int
 -> Maybe Text
 -> FilePath
 -> Maybe FilePath
 -> [FilePath]
 -> Maybe FilePath
 -> Bool
 -> Int
 -> Bool
 -> Bool
 -> Verbosity
 -> Bool
 -> Maybe FilePath
 -> Bool
 -> Bool
 -> ReferenceLocation
 -> Int
 -> WrapOption
 -> Int
 -> [Filter]
 -> ObfuscationMethod
 -> Text
 -> [Text]
 -> Maybe FilePath
 -> CiteMethod
 -> Bool
 -> Maybe FilePath
 -> [FilePath]
 -> Maybe Int
 -> Bool
 -> Bool
 -> Bool
 -> Text
 -> Maybe FilePath
 -> TrackChanges
 -> Bool
 -> Maybe Text
 -> [FilePath]
 -> IpynbOutput
 -> [FilePath]
 -> [FilePath]
 -> [FilePath]
 -> [FilePath]
 -> [(Text, Text)]
 -> Bool
 -> LineEnding
 -> Bool
 -> Maybe FilePath
 -> [FilePath]
 -> Maybe FilePath
 -> Bool
 -> Opt)
-> Parser Int
-> Parser
     (Bool
      -> Bool
      -> Maybe Text
      -> Maybe Text
      -> Bool
      -> Int
      -> Maybe FilePath
      -> Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"tab-stop" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Int
optTabStop Opt
defaultOpts
       Parser
  (Bool
   -> Bool
   -> Maybe Text
   -> Maybe Text
   -> Bool
   -> Int
   -> Maybe FilePath
   -> Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Maybe Text
      -> Maybe Text
      -> Bool
      -> Int
      -> Maybe FilePath
      -> Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"preserve-tabs" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optPreserveTabs Opt
defaultOpts
       Parser
  (Bool
   -> Maybe Text
   -> Maybe Text
   -> Bool
   -> Int
   -> Maybe FilePath
   -> Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Bool
      -> Int
      -> Maybe FilePath
      -> Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"standalone" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optStandalone Opt
defaultOpts
       Parser
  (Maybe Text
   -> Maybe Text
   -> Bool
   -> Int
   -> Maybe FilePath
   -> Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Bool
      -> Int
      -> Maybe FilePath
      -> Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"from"
       Parser
  (Maybe Text
   -> Bool
   -> Int
   -> Maybe FilePath
   -> Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe Text)
-> Parser
     (Bool
      -> Int
      -> Maybe FilePath
      -> Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"to"
       Parser
  (Bool
   -> Int
   -> Maybe FilePath
   -> Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Int
      -> Maybe FilePath
      -> Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"table-of-contents" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optTableOfContents Opt
defaultOpts
       Parser
  (Int
   -> Maybe FilePath
   -> Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Int
-> Parser
     (Maybe FilePath
      -> Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"shift-heading-level-by" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Int
optShiftHeadingLevelBy Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (Context Text
      -> Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"template"
       Parser
  (Context Text
   -> Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Context Text)
-> Parser
     (Meta
      -> [FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe (Context Text))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"variables" Parser (Maybe (Context Text))
-> Context Text -> Parser (Context Text)
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Context Text
optVariables Opt
defaultOpts
       Parser
  (Meta
   -> [FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Meta
-> Parser
     ([FilePath]
      -> Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Meta)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"metadata" Parser (Maybe Meta) -> Meta -> Parser Meta
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Meta
optMetadata Opt
defaultOpts
       Parser
  ([FilePath]
   -> Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     (Maybe FilePath
      -> Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"metadata-files" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optMetadataFiles Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (Maybe [FilePath]
      -> Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"output-file"
       Parser
  (Maybe [FilePath]
   -> Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe [FilePath])
-> Parser
     (Bool
      -> [Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"input-files"
       Parser
  (Bool
   -> [Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     ([Int]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"number-sections" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optNumberSections Opt
defaultOpts
       Parser
  ([Int]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [Int]
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [Int])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"number-offset" Parser (Maybe [Int]) -> [Int] -> Parser [Int]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [Int]
optNumberOffset Opt
defaultOpts
       Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"section-divs" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optSectionDivs Opt
defaultOpts
       Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"incremental" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optIncremental Opt
defaultOpts
       Parser
  (Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"self-contained" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optSelfContained Opt
defaultOpts
       Parser
  (Bool
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"embed-resources" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optEmbedResources Opt
defaultOpts
       Parser
  (Bool
   -> Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Maybe Text
      -> [FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"html-q-tags" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optHtmlQTags Opt
defaultOpts
       Parser
  (Maybe Text
   -> [FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe Text)
-> Parser
     ([FilePath]
      -> TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"highlight-style"
       Parser
  ([FilePath]
   -> TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     (TopLevelDivision
      -> HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"syntax-definitions" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optSyntaxDefinitions Opt
defaultOpts
       Parser
  (TopLevelDivision
   -> HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser TopLevelDivision
-> Parser
     (HTMLMathMethod
      -> Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe TopLevelDivision)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"top-level-division" Parser (Maybe TopLevelDivision)
-> TopLevelDivision -> Parser TopLevelDivision
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> TopLevelDivision
optTopLevelDivision Opt
defaultOpts
       Parser
  (HTMLMathMethod
   -> Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser HTMLMathMethod
-> Parser
     (Maybe FilePath
      -> Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe HTMLMathMethod)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"html-math-method" Parser (Maybe HTMLMathMethod)
-> HTMLMathMethod -> Parser HTMLMathMethod
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> HTMLMathMethod
optHTMLMathMethod Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (Maybe FilePath
      -> Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"abbreviations"
       Parser
  (Maybe FilePath
   -> Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (Int
      -> Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"reference-doc"
       Parser
  (Int
   -> Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Int
-> Parser
     (Maybe Text
      -> FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"split-level") Parser (Maybe Int) -> Parser (Maybe Int) -> Parser (Maybe Int)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"epub-chapter-level"))
             Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Int
optSplitLevel Opt
defaultOpts
       Parser
  (Maybe Text
   -> FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe Text)
-> Parser
     (FilePath
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"chunk-template"
       Parser
  (FilePath
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser FilePath
-> Parser
     (Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"epub-subdirectory" Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> FilePath
optEpubSubdirectory Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     ([FilePath]
      -> Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"epub-metadata"
       Parser
  ([FilePath]
   -> Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     (Maybe FilePath
      -> Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"epub-fonts" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optEpubFonts Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (Bool
      -> Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"epub-cover-image"
       Parser
  (Bool
   -> Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Int
      -> Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"epub-title-page" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optEpubTitlePage Opt
defaultOpts
       Parser
  (Int
   -> Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Int
-> Parser
     (Bool
      -> Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"toc-depth" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Int
optTOCDepth Opt
defaultOpts
       Parser
  (Bool
   -> Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"dump-args" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optDumpArgs Opt
defaultOpts
       Parser
  (Bool
   -> Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Verbosity
      -> Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ignore-args" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optIgnoreArgs Opt
defaultOpts
       Parser
  (Verbosity
   -> Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Verbosity
-> Parser
     (Bool
      -> Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Verbosity)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"verbosity" Parser (Maybe Verbosity) -> Verbosity -> Parser Verbosity
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Verbosity
optVerbosity Opt
defaultOpts
       Parser
  (Bool
   -> Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Maybe FilePath
      -> Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"trace" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optTrace Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (Bool
      -> Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"log-file"
       Parser
  (Bool
   -> Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"fail-if-warnings" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optFailIfWarnings Opt
defaultOpts
       Parser
  (Bool
   -> ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (ReferenceLocation
      -> Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"reference-links" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optReferenceLinks Opt
defaultOpts
       Parser
  (ReferenceLocation
   -> Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser ReferenceLocation
-> Parser
     (Int
      -> WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe ReferenceLocation)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"reference-location" Parser (Maybe ReferenceLocation)
-> ReferenceLocation -> Parser ReferenceLocation
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> ReferenceLocation
optReferenceLocation Opt
defaultOpts
       Parser
  (Int
   -> WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Int
-> Parser
     (WrapOption
      -> Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"dpi" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Int
optDpi Opt
defaultOpts
       Parser
  (WrapOption
   -> Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser WrapOption
-> Parser
     (Int
      -> [Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe WrapOption)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"wrap" Parser (Maybe WrapOption) -> WrapOption -> Parser WrapOption
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> WrapOption
optWrap Opt
defaultOpts
       Parser
  (Int
   -> [Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Int
-> Parser
     ([Filter]
      -> ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"columns" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Int
optColumns Opt
defaultOpts
       Parser
  ([Filter]
   -> ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [Filter]
-> Parser
     (ObfuscationMethod
      -> Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [Filter])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"filters" Parser (Maybe [Filter]) -> [Filter] -> Parser [Filter]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [Filter]
optFilters Opt
defaultOpts
       Parser
  (ObfuscationMethod
   -> Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser ObfuscationMethod
-> Parser
     (Text
      -> [Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe ObfuscationMethod)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"email-obfuscation" Parser (Maybe ObfuscationMethod)
-> ObfuscationMethod -> Parser ObfuscationMethod
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> ObfuscationMethod
optEmailObfuscation Opt
defaultOpts
       Parser
  (Text
   -> [Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Text
-> Parser
     ([Text]
      -> Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"identifier-prefix" Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Text
optIdentifierPrefix Opt
defaultOpts
       Parser
  ([Text]
   -> Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [Text]
-> Parser
     (Maybe FilePath
      -> CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"indented-code-classes" Parser (Maybe [Text]) -> [Text] -> Parser [Text]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [Text]
optIndentedCodeClasses Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (CiteMethod
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"data-dir"
       Parser
  (CiteMethod
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser CiteMethod
-> Parser
     (Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe CiteMethod)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"cite-method" Parser (Maybe CiteMethod) -> CiteMethod -> Parser CiteMethod
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> CiteMethod
optCiteMethod Opt
defaultOpts
       Parser
  (Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Maybe FilePath
      -> [FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"listings" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optListings Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> [FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     ([FilePath]
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"pdf-engine"
       Parser
  ([FilePath]
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     (Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"pdf-engine-opts" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optPdfEngineOpts Opt
defaultOpts
       Parser
  (Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe Int)
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"slide-level"
       Parser
  (Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"setext-headers" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optSetextHeaders Opt
defaultOpts
       Parser
  (Bool
   -> Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Bool
      -> Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"list-tables" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optListTables Opt
defaultOpts
       Parser
  (Bool
   -> Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Text
      -> Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ascii" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optAscii Opt
defaultOpts
       Parser
  (Text
   -> Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Text
-> Parser
     (Maybe FilePath
      -> TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"default-image-extension" Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Text
optDefaultImageExtension Opt
defaultOpts
       Parser
  (Maybe FilePath
   -> TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe FilePath)
-> Parser
     (TrackChanges
      -> Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"extract-media"
       Parser
  (TrackChanges
   -> Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser TrackChanges
-> Parser
     (Bool
      -> Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe TrackChanges)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"track-changes" Parser (Maybe TrackChanges) -> TrackChanges -> Parser TrackChanges
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> TrackChanges
optTrackChanges Opt
defaultOpts
       Parser
  (Bool
   -> Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (Maybe Text
      -> [FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"file-scope" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optFileScope Opt
defaultOpts
       Parser
  (Maybe Text
   -> [FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser (Maybe Text)
-> Parser
     ([FilePath]
      -> IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe (Maybe Text))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"title-prefix" Parser (Maybe (Maybe Text)) -> Maybe Text -> Parser (Maybe Text)
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Maybe Text
optTitlePrefix Opt
defaultOpts
       Parser
  ([FilePath]
   -> IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     (IpynbOutput
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"css" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optCss Opt
defaultOpts
       Parser
  (IpynbOutput
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser IpynbOutput
-> Parser
     ([FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe IpynbOutput)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ipynb-output" Parser (Maybe IpynbOutput) -> IpynbOutput -> Parser IpynbOutput
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> IpynbOutput
optIpynbOutput Opt
defaultOpts
       Parser
  ([FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     ([FilePath]
      -> [FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"include-before-body" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optIncludeBeforeBody Opt
defaultOpts
       Parser
  ([FilePath]
   -> [FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     ([FilePath]
      -> [FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"include-after-body" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optIncludeAfterBody Opt
defaultOpts
       Parser
  ([FilePath]
   -> [FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     ([FilePath]
      -> [(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"include-in-header" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optIncludeInHeader Opt
defaultOpts
       Parser
  ([FilePath]
   -> [(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [FilePath]
-> Parser
     ([(Text, Text)]
      -> Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"resource-path" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optResourcePath Opt
defaultOpts
       Parser
  ([(Text, Text)]
   -> Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser [(Text, Text)]
-> Parser
     (Bool
      -> LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [(Text, Text)])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"request-headers" Parser (Maybe [(Text, Text)])
-> [(Text, Text)] -> Parser [(Text, Text)]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [(Text, Text)]
optRequestHeaders Opt
defaultOpts
       Parser
  (Bool
   -> LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser Bool
-> Parser
     (LineEnding
      -> Bool
      -> Maybe FilePath
      -> [FilePath]
      -> Maybe FilePath
      -> Bool
      -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"no-check-certificate" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optNoCheckCertificate Opt
defaultOpts
       Parser
  (LineEnding
   -> Bool
   -> Maybe FilePath
   -> [FilePath]
   -> Maybe FilePath
   -> Bool
   -> Opt)
-> Parser LineEnding
-> Parser
     (Bool
      -> Maybe FilePath -> [FilePath] -> Maybe FilePath -> Bool -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe LineEnding)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"eol" Parser (Maybe LineEnding) -> LineEnding -> Parser LineEnding
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> LineEnding
optEol Opt
defaultOpts
       Parser
  (Bool
   -> Maybe FilePath -> [FilePath] -> Maybe FilePath -> Bool -> Opt)
-> Parser Bool
-> Parser
     (Maybe FilePath -> [FilePath] -> Maybe FilePath -> Bool -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"strip-comments" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optStripComments Opt
defaultOpts
       Parser
  (Maybe FilePath -> [FilePath] -> Maybe FilePath -> Bool -> Opt)
-> Parser (Maybe FilePath)
-> Parser ([FilePath] -> Maybe FilePath -> Bool -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"csl"
       Parser ([FilePath] -> Maybe FilePath -> Bool -> Opt)
-> Parser [FilePath] -> Parser (Maybe FilePath -> Bool -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bibliography" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> [FilePath]
optBibliography Opt
defaultOpts
       Parser (Maybe FilePath -> Bool -> Opt)
-> Parser (Maybe FilePath) -> Parser (Bool -> Opt)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"citation-abbreviations"
       Parser (Bool -> Opt) -> Parser Bool -> Parser Opt
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"sandbox" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Opt -> Bool
optSandbox Opt
defaultOpts
instance ToJSON Opt where
 toJSON :: Opt -> Value
toJSON = Options -> Opt -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions{
                                 fieldLabelModifier :: ShowS
fieldLabelModifier = Char -> ShowS
camelTo2 Char
'-' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
3,
                                 omitNothingFields :: Bool
omitNothingFields = Bool
True }
instance FromJSON (Opt -> Opt) where
  parseJSON :: Value -> Parser (Opt -> Opt)
parseJSON (Object Object
m) =
    case Value -> Result (Map Text Value)
forall a. FromJSON a => Value -> Result a
fromJSON (Object -> Value
Object Object
m) of
      Error FilePath
err' -> FilePath -> Parser (Opt -> Opt)
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
err'
      Success (Map Text Value
m' :: M.Map Text Value) -> ((Text, Value) -> Parser (Opt -> Opt))
-> [(Text, Value)] -> Parser (Opt -> Opt)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (b -> b)) -> [a] -> m (b -> b)
chain (Text, Value) -> Parser (Opt -> Opt)
doOpt (Map Text Value -> [(Text, Value)]
forall k a. Map k a -> [(k, a)]
M.toList Map Text Value
m')
  parseJSON Value
_ = FilePath -> Parser (Opt -> Opt)
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Expected a mapping"
data DefaultsState = DefaultsState
    {
      DefaultsState -> Maybe FilePath
curDefaults      :: Maybe FilePath 
    , DefaultsState -> [[FilePath]]
inheritanceGraph :: [[FilePath]]   
    } deriving (Int -> DefaultsState -> ShowS
[DefaultsState] -> ShowS
DefaultsState -> FilePath
(Int -> DefaultsState -> ShowS)
-> (DefaultsState -> FilePath)
-> ([DefaultsState] -> ShowS)
-> Show DefaultsState
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DefaultsState -> ShowS
showsPrec :: Int -> DefaultsState -> ShowS
$cshow :: DefaultsState -> FilePath
show :: DefaultsState -> FilePath
$cshowList :: [DefaultsState] -> ShowS
showList :: [DefaultsState] -> ShowS
Show)
instance (PandocMonad m, MonadIO m)
      => FromJSON (Opt -> StateT DefaultsState m Opt) where
  parseJSON :: Value -> Parser (Opt -> StateT DefaultsState m Opt)
parseJSON (Object Object
o) =
    case Value -> Result (Map Text Value)
forall a. FromJSON a => Value -> Result a
fromJSON (Object -> Value
Object Object
o) of
      Error FilePath
err' -> FilePath -> Parser (Opt -> StateT DefaultsState m Opt)
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
err'
      Success (Map Text Value
opts :: M.Map Text Value) -> do
        Maybe FilePath
dataDir <- case Text -> Map Text Value -> Maybe Value
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
"data-dir" Map Text Value
opts of
          Maybe Value
Nothing -> Maybe FilePath -> Parser (Maybe FilePath)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
          Just Value
v -> FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath)
-> (Text -> FilePath) -> Text -> Maybe FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack (Text -> Maybe FilePath) -> Parser Text -> Parser (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
        Opt -> StateT DefaultsState m Opt
f <- [(Text, Value)] -> Parser (Opt -> StateT DefaultsState m Opt)
forall (m :: * -> *).
Monad m =>
[(Text, Value)] -> Parser (Opt -> StateT DefaultsState m Opt)
parseOptions (Map Text Value -> [(Text, Value)]
forall k a. Map k a -> [(k, a)]
M.toList Map Text Value
opts)
        case Text -> Map Text Value -> Maybe Value
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
"defaults" Map Text Value
opts of
          Just Value
v -> do
            Opt -> StateT DefaultsState m Opt
g <- Value
-> Maybe FilePath -> Parser (Opt -> StateT DefaultsState m Opt)
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Value
-> Maybe FilePath -> Parser (Opt -> StateT DefaultsState m Opt)
parseDefaults Value
v Maybe FilePath
dataDir
            (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return  ((Opt -> StateT DefaultsState m Opt)
 -> Parser (Opt -> StateT DefaultsState m Opt))
-> (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a b. (a -> b) -> a -> b
$ Opt -> StateT DefaultsState m Opt
g (Opt -> StateT DefaultsState m Opt)
-> (Opt -> StateT DefaultsState m Opt)
-> Opt
-> StateT DefaultsState m Opt
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Opt -> StateT DefaultsState m Opt
f (Opt -> StateT DefaultsState m Opt)
-> (Opt -> StateT DefaultsState m Opt)
-> Opt
-> StateT DefaultsState m Opt
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Opt -> StateT DefaultsState m Opt
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Opt -> StateT DefaultsState m Opt
resolveVarsInOpt
          Maybe Value
Nothing -> (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Opt -> StateT DefaultsState m Opt)
 -> Parser (Opt -> StateT DefaultsState m Opt))
-> (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a b. (a -> b) -> a -> b
$ Opt -> StateT DefaultsState m Opt
f (Opt -> StateT DefaultsState m Opt)
-> (Opt -> StateT DefaultsState m Opt)
-> Opt
-> StateT DefaultsState m Opt
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Opt -> StateT DefaultsState m Opt
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Opt -> StateT DefaultsState m Opt
resolveVarsInOpt
  parseJSON Value
_ = FilePath -> Parser (Opt -> StateT DefaultsState m Opt)
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Expected a mapping"
resolveVarsInOpt :: forall m. (PandocMonad m, MonadIO m)
                 => Opt -> StateT DefaultsState m Opt
resolveVarsInOpt :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Opt -> StateT DefaultsState m Opt
resolveVarsInOpt
    opt :: Opt
opt@Opt
    { optTemplate :: Opt -> Maybe FilePath
optTemplate              = Maybe FilePath
oTemplate
    , optMetadataFiles :: Opt -> [FilePath]
optMetadataFiles         = [FilePath]
oMetadataFiles
    , optOutputFile :: Opt -> Maybe FilePath
optOutputFile            = Maybe FilePath
oOutputFile
    , optInputFiles :: Opt -> Maybe [FilePath]
optInputFiles            = Maybe [FilePath]
oInputFiles
    , optSyntaxDefinitions :: Opt -> [FilePath]
optSyntaxDefinitions     = [FilePath]
oSyntaxDefinitions
    , optAbbreviations :: Opt -> Maybe FilePath
optAbbreviations         = Maybe FilePath
oAbbreviations
    , optReferenceDoc :: Opt -> Maybe FilePath
optReferenceDoc          = Maybe FilePath
oReferenceDoc
    , optEpubMetadata :: Opt -> Maybe FilePath
optEpubMetadata          = Maybe FilePath
oEpubMetadata
    , optEpubFonts :: Opt -> [FilePath]
optEpubFonts             = [FilePath]
oEpubFonts
    , optEpubCoverImage :: Opt -> Maybe FilePath
optEpubCoverImage        = Maybe FilePath
oEpubCoverImage
    , optLogFile :: Opt -> Maybe FilePath
optLogFile               = Maybe FilePath
oLogFile
    , optFilters :: Opt -> [Filter]
optFilters               = [Filter]
oFilters
    , optDataDir :: Opt -> Maybe FilePath
optDataDir               = Maybe FilePath
oDataDir
    , optExtractMedia :: Opt -> Maybe FilePath
optExtractMedia          = Maybe FilePath
oExtractMedia
    , optCss :: Opt -> [FilePath]
optCss                   = [FilePath]
oCss
    , optIncludeBeforeBody :: Opt -> [FilePath]
optIncludeBeforeBody     = [FilePath]
oIncludeBeforeBody
    , optIncludeAfterBody :: Opt -> [FilePath]
optIncludeAfterBody      = [FilePath]
oIncludeAfterBody
    , optIncludeInHeader :: Opt -> [FilePath]
optIncludeInHeader       = [FilePath]
oIncludeInHeader
    , optResourcePath :: Opt -> [FilePath]
optResourcePath          = [FilePath]
oResourcePath
    , optCSL :: Opt -> Maybe FilePath
optCSL                   = Maybe FilePath
oCSL
    , optBibliography :: Opt -> [FilePath]
optBibliography          = [FilePath]
oBibliography
    , optCitationAbbreviations :: Opt -> Maybe FilePath
optCitationAbbreviations = Maybe FilePath
oCitationAbbreviations
    , optPdfEngine :: Opt -> Maybe FilePath
optPdfEngine             = Maybe FilePath
oPdfEngine
    , optHighlightStyle :: Opt -> Maybe Text
optHighlightStyle        = Maybe Text
oHighlightStyle
    }
  = do
      Maybe FilePath
oTemplate' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oTemplate
      [FilePath]
oMetadataFiles' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oMetadataFiles
      Maybe FilePath
oOutputFile' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oOutputFile
      Maybe [FilePath]
oInputFiles' <- ([FilePath] -> StateT DefaultsState m [FilePath])
-> Maybe [FilePath] -> StateT DefaultsState m (Maybe [FilePath])
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM ((FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars) Maybe [FilePath]
oInputFiles
      [FilePath]
oSyntaxDefinitions' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oSyntaxDefinitions
      Maybe FilePath
oAbbreviations' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oAbbreviations
      Maybe FilePath
oReferenceDoc' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oReferenceDoc
      Maybe FilePath
oEpubMetadata' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oEpubMetadata
      [FilePath]
oEpubFonts' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oEpubFonts
      Maybe FilePath
oEpubCoverImage' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oEpubCoverImage
      Maybe FilePath
oLogFile' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oLogFile
      [Filter]
oFilters' <- (Filter -> StateT DefaultsState m Filter)
-> [Filter] -> StateT DefaultsState m [Filter]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Filter -> StateT DefaultsState m Filter
resolveVarsInFilter [Filter]
oFilters
      Maybe FilePath
oDataDir' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oDataDir
      Maybe FilePath
oExtractMedia' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oExtractMedia
      [FilePath]
oCss' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oCss
      [FilePath]
oIncludeBeforeBody' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oIncludeBeforeBody
      [FilePath]
oIncludeAfterBody' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oIncludeAfterBody
      [FilePath]
oIncludeInHeader' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oIncludeInHeader
      [FilePath]
oResourcePath' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oResourcePath
      Maybe FilePath
oCSL' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oCSL
      [FilePath]
oBibliography' <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars [FilePath]
oBibliography
      Maybe FilePath
oCitationAbbreviations' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oCitationAbbreviations
      Maybe FilePath
oPdfEngine' <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oPdfEngine
      Maybe Text
oHighlightStyle' <- (Text -> StateT DefaultsState m Text)
-> Maybe Text -> StateT DefaultsState m (Maybe Text)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM ((FilePath -> Text)
-> StateT DefaultsState m FilePath -> StateT DefaultsState m Text
forall a b.
(a -> b) -> StateT DefaultsState m a -> StateT DefaultsState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> Text
T.pack (StateT DefaultsState m FilePath -> StateT DefaultsState m Text)
-> (Text -> StateT DefaultsState m FilePath)
-> Text
-> StateT DefaultsState m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> StateT DefaultsState m FilePath
resolveVars (FilePath -> StateT DefaultsState m FilePath)
-> (Text -> FilePath) -> Text -> StateT DefaultsState m FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack) Maybe Text
oHighlightStyle
      Opt -> StateT DefaultsState m Opt
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Opt
opt{ optTemplate :: Maybe FilePath
optTemplate              = Maybe FilePath
oTemplate'
                , optMetadataFiles :: [FilePath]
optMetadataFiles         = [FilePath]
oMetadataFiles'
                , optOutputFile :: Maybe FilePath
optOutputFile            = Maybe FilePath
oOutputFile'
                , optInputFiles :: Maybe [FilePath]
optInputFiles            = Maybe [FilePath]
oInputFiles'
                , optSyntaxDefinitions :: [FilePath]
optSyntaxDefinitions     = [FilePath]
oSyntaxDefinitions'
                , optAbbreviations :: Maybe FilePath
optAbbreviations         = Maybe FilePath
oAbbreviations'
                , optReferenceDoc :: Maybe FilePath
optReferenceDoc          = Maybe FilePath
oReferenceDoc'
                , optEpubMetadata :: Maybe FilePath
optEpubMetadata          = Maybe FilePath
oEpubMetadata'
                , optEpubFonts :: [FilePath]
optEpubFonts             = [FilePath]
oEpubFonts'
                , optEpubCoverImage :: Maybe FilePath
optEpubCoverImage        = Maybe FilePath
oEpubCoverImage'
                , optLogFile :: Maybe FilePath
optLogFile               = Maybe FilePath
oLogFile'
                , optFilters :: [Filter]
optFilters               = [Filter]
oFilters'
                , optDataDir :: Maybe FilePath
optDataDir               = Maybe FilePath
oDataDir'
                , optExtractMedia :: Maybe FilePath
optExtractMedia          = Maybe FilePath
oExtractMedia'
                , optCss :: [FilePath]
optCss                   = [FilePath]
oCss'
                , optIncludeBeforeBody :: [FilePath]
optIncludeBeforeBody     = [FilePath]
oIncludeBeforeBody'
                , optIncludeAfterBody :: [FilePath]
optIncludeAfterBody      = [FilePath]
oIncludeAfterBody'
                , optIncludeInHeader :: [FilePath]
optIncludeInHeader       = [FilePath]
oIncludeInHeader'
                , optResourcePath :: [FilePath]
optResourcePath          = [FilePath]
oResourcePath'
                , optCSL :: Maybe FilePath
optCSL                   = Maybe FilePath
oCSL'
                , optBibliography :: [FilePath]
optBibliography          = [FilePath]
oBibliography'
                , optCitationAbbreviations :: Maybe FilePath
optCitationAbbreviations = Maybe FilePath
oCitationAbbreviations'
                , optPdfEngine :: Maybe FilePath
optPdfEngine             = Maybe FilePath
oPdfEngine'
                , optHighlightStyle :: Maybe Text
optHighlightStyle        = Maybe Text
oHighlightStyle'
                }
 where
  resolveVars :: FilePath -> StateT DefaultsState m FilePath
  resolveVars :: FilePath -> StateT DefaultsState m FilePath
resolveVars [] = FilePath -> StateT DefaultsState m FilePath
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return []
  resolveVars (Char
'$':Char
'{':FilePath
xs) =
    let (FilePath
ys, FilePath
zs) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'}') FilePath
xs
     in if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
zs
           then FilePath -> StateT DefaultsState m FilePath
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> StateT DefaultsState m FilePath)
-> FilePath -> StateT DefaultsState m FilePath
forall a b. (a -> b) -> a -> b
$ Char
'$'Char -> ShowS
forall a. a -> [a] -> [a]
:Char
'{'Char -> ShowS
forall a. a -> [a] -> [a]
:FilePath
xs
           else do
             FilePath
val <- FilePath -> StateT DefaultsState m FilePath
lookupEnv' FilePath
ys
             (FilePath
val FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS
-> StateT DefaultsState m FilePath
-> StateT DefaultsState m FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> StateT DefaultsState m FilePath
resolveVars (Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 FilePath
zs)
  resolveVars (Char
c:FilePath
cs) = (Char
cChar -> ShowS
forall a. a -> [a] -> [a]
:) ShowS
-> StateT DefaultsState m FilePath
-> StateT DefaultsState m FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> StateT DefaultsState m FilePath
resolveVars FilePath
cs
  lookupEnv' :: String -> StateT DefaultsState m String
  lookupEnv' :: FilePath -> StateT DefaultsState m FilePath
lookupEnv' FilePath
"." = do
    Maybe FilePath
mbCurDefaults <- (DefaultsState -> Maybe FilePath)
-> StateT DefaultsState m (Maybe FilePath)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DefaultsState -> Maybe FilePath
curDefaults
    StateT DefaultsState m FilePath
-> (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath
-> StateT DefaultsState m FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FilePath -> StateT DefaultsState m FilePath
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"")
          (ShowS
-> StateT DefaultsState m FilePath
-> StateT DefaultsState m FilePath
forall a b.
(a -> b) -> StateT DefaultsState m a -> StateT DefaultsState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShowS
takeDirectory (StateT DefaultsState m FilePath
 -> StateT DefaultsState m FilePath)
-> (FilePath -> StateT DefaultsState m FilePath)
-> FilePath
-> StateT DefaultsState m FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO FilePath -> StateT DefaultsState m FilePath
forall a. IO a -> StateT DefaultsState m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilePath -> StateT DefaultsState m FilePath)
-> (FilePath -> IO FilePath)
-> FilePath
-> StateT DefaultsState m FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath)
          Maybe FilePath
mbCurDefaults
  lookupEnv' FilePath
"USERDATA" = do
    Maybe FilePath
mbodatadir <- (FilePath -> StateT DefaultsState m FilePath)
-> Maybe FilePath -> StateT DefaultsState m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM FilePath -> StateT DefaultsState m FilePath
resolveVars Maybe FilePath
oDataDir
    Maybe FilePath
mbdatadir  <- StateT DefaultsState m (Maybe FilePath)
forall (m :: * -> *). PandocMonad m => m (Maybe FilePath)
getUserDataDir
    FilePath
defdatadir <- IO FilePath -> StateT DefaultsState m FilePath
forall a. IO a -> StateT DefaultsState m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO FilePath
defaultUserDataDir
    FilePath -> StateT DefaultsState m FilePath
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> StateT DefaultsState m FilePath)
-> FilePath -> StateT DefaultsState m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
defdatadir (Maybe FilePath
mbodatadir Maybe FilePath -> Maybe FilePath -> Maybe FilePath
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FilePath
mbdatadir)
  lookupEnv' FilePath
v = do
    Maybe FilePath
mbval <- (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> FilePath
T.unpack (Maybe Text -> Maybe FilePath)
-> StateT DefaultsState m (Maybe Text)
-> StateT DefaultsState m (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> StateT DefaultsState m (Maybe Text)
forall (m :: * -> *). PandocMonad m => Text -> m (Maybe Text)
lookupEnv (FilePath -> Text
T.pack FilePath
v)
    case Maybe FilePath
mbval of
      Maybe FilePath
Nothing -> do
        LogMessage -> StateT DefaultsState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> StateT DefaultsState m ())
-> LogMessage -> StateT DefaultsState m ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
EnvironmentVariableUndefined (FilePath -> Text
T.pack FilePath
v)
        FilePath -> StateT DefaultsState m FilePath
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
forall a. Monoid a => a
mempty
      Just FilePath
x  -> FilePath -> StateT DefaultsState m FilePath
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
x
  resolveVarsInFilter :: Filter -> StateT DefaultsState m Filter
resolveVarsInFilter (JSONFilter FilePath
fp) =
    FilePath -> Filter
JSONFilter (FilePath -> Filter)
-> StateT DefaultsState m FilePath -> StateT DefaultsState m Filter
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> StateT DefaultsState m FilePath
resolveVars FilePath
fp
  resolveVarsInFilter (LuaFilter FilePath
fp) =
    FilePath -> Filter
LuaFilter (FilePath -> Filter)
-> StateT DefaultsState m FilePath -> StateT DefaultsState m Filter
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> StateT DefaultsState m FilePath
resolveVars FilePath
fp
  resolveVarsInFilter Filter
CiteprocFilter = Filter -> StateT DefaultsState m Filter
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Filter
CiteprocFilter
parseDefaults :: (PandocMonad m, MonadIO m)
              => Value
              -> Maybe FilePath
              -> Parser (Opt -> StateT DefaultsState m Opt)
parseDefaults :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Value
-> Maybe FilePath -> Parser (Opt -> StateT DefaultsState m Opt)
parseDefaults Value
n Maybe FilePath
dataDir = Value -> Parser [FilePath]
parseDefsNames Value
n Parser [FilePath]
-> ([FilePath] -> Parser (Opt -> StateT DefaultsState m Opt))
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[FilePath]
ds -> (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Opt -> StateT DefaultsState m Opt)
 -> Parser (Opt -> StateT DefaultsState m Opt))
-> (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a b. (a -> b) -> a -> b
$ \Opt
o -> do
  
  FilePath
defsParent <- (DefaultsState -> FilePath) -> StateT DefaultsState m FilePath
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets ((DefaultsState -> FilePath) -> StateT DefaultsState m FilePath)
-> (DefaultsState -> FilePath) -> StateT DefaultsState m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"" (Maybe FilePath -> FilePath)
-> (DefaultsState -> Maybe FilePath) -> DefaultsState -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DefaultsState -> Maybe FilePath
curDefaults
  
  [FilePath]
defsChildren <- (FilePath -> StateT DefaultsState m FilePath)
-> [FilePath] -> StateT DefaultsState m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Maybe FilePath -> FilePath -> StateT DefaultsState m FilePath
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Maybe FilePath -> FilePath -> m FilePath
fullDefaultsPath Maybe FilePath
dataDir) [FilePath]
ds
  
  [[FilePath]]
defsGraph <- (DefaultsState -> [[FilePath]])
-> StateT DefaultsState m [[FilePath]]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DefaultsState -> [[FilePath]]
inheritanceGraph
  let defsGraphExp :: [[FilePath]]
defsGraphExp = [[FilePath]] -> [FilePath] -> FilePath -> [[FilePath]]
forall a. Ord a => [[a]] -> [a] -> a -> [[a]]
expand [[FilePath]]
defsGraph [FilePath]
defsChildren FilePath
defsParent
  (DefaultsState -> DefaultsState) -> StateT DefaultsState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DefaultsState -> DefaultsState) -> StateT DefaultsState m ())
-> (DefaultsState -> DefaultsState) -> StateT DefaultsState m ()
forall a b. (a -> b) -> a -> b
$ \DefaultsState
defsState -> DefaultsState
defsState{ inheritanceGraph :: [[FilePath]]
inheritanceGraph = [[FilePath]]
defsGraphExp }
  
  if [[FilePath]] -> Bool
forall a. Ord a => [[a]] -> Bool
cyclic [[FilePath]]
defsGraphExp
    then PandocError -> StateT DefaultsState m Opt
forall a. PandocError -> StateT DefaultsState m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> StateT DefaultsState m Opt)
-> PandocError -> StateT DefaultsState m Opt
forall a b. (a -> b) -> a -> b
$
      Text -> PandocError
PandocSomeError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$
        FilePath
"Error: Circular defaults file reference in " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++
        FilePath
"'" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
defsParent FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"'"
    else (Opt -> FilePath -> StateT DefaultsState m Opt)
-> Opt -> [FilePath] -> StateT DefaultsState m Opt
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM Opt -> FilePath -> StateT DefaultsState m Opt
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Opt -> FilePath -> StateT DefaultsState m Opt
applyDefaults Opt
o [FilePath]
defsChildren
  where parseDefsNames :: Value -> Parser [FilePath]
parseDefsNames Value
x = (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x Parser [Text] -> ([Text] -> Parser [FilePath]) -> Parser [FilePath]
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
xs -> [FilePath] -> Parser [FilePath]
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> Parser [FilePath])
-> [FilePath] -> Parser [FilePath]
forall a b. (a -> b) -> a -> b
$ (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
xs)
                       Parser [FilePath] -> Parser [FilePath] -> Parser [FilePath]
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x Parser Text -> (Text -> Parser [FilePath]) -> Parser [FilePath]
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x' -> [FilePath] -> Parser [FilePath]
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text -> FilePath
unpack Text
x'])
parseOptions :: Monad m
             => [(Text, Value)]
             -> Parser (Opt -> StateT DefaultsState m Opt)
parseOptions :: forall (m :: * -> *).
Monad m =>
[(Text, Value)] -> Parser (Opt -> StateT DefaultsState m Opt)
parseOptions [(Text, Value)]
ns = do
  Opt -> Opt
f <- ((Text, Value) -> Parser (Opt -> Opt))
-> [(Text, Value)] -> Parser (Opt -> Opt)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (b -> b)) -> [a] -> m (b -> b)
chain (Text, Value) -> Parser (Opt -> Opt)
doOpt' [(Text, Value)]
ns
  (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Opt -> StateT DefaultsState m Opt)
 -> Parser (Opt -> StateT DefaultsState m Opt))
-> (Opt -> StateT DefaultsState m Opt)
-> Parser (Opt -> StateT DefaultsState m Opt)
forall a b. (a -> b) -> a -> b
$ Opt -> StateT DefaultsState m Opt
forall a. a -> StateT DefaultsState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Opt -> StateT DefaultsState m Opt)
-> (Opt -> Opt) -> Opt -> StateT DefaultsState m Opt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Opt -> Opt
f
chain :: Monad m => (a -> m (b -> b)) -> [a] -> m (b -> b)
chain :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (b -> b)) -> [a] -> m (b -> b)
chain a -> m (b -> b)
f = ((b -> b) -> a -> m (b -> b)) -> (b -> b) -> [a] -> m (b -> b)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (b -> b) -> a -> m (b -> b)
forall {a}. (a -> b) -> a -> m (a -> b)
g b -> b
forall a. a -> a
id
  where g :: (a -> b) -> a -> m (a -> b)
g a -> b
o a
n = a -> m (b -> b)
f a
n m (b -> b) -> ((b -> b) -> m (a -> b)) -> m (a -> b)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \b -> b
o' -> (a -> b) -> m (a -> b)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((a -> b) -> m (a -> b)) -> (a -> b) -> m (a -> b)
forall a b. (a -> b) -> a -> b
$ b -> b
o' (b -> b) -> (a -> b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
o
doOpt' :: (Text, Value) -> Parser (Opt -> Opt)
doOpt' :: (Text, Value) -> Parser (Opt -> Opt)
doOpt' (Text
k,Value
v) = do
  case Text
k of
    Text
"defaults" -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Opt -> Opt
forall a. a -> a
id
    Text
_ -> (Text, Value) -> Parser (Opt -> Opt)
doOpt (Text
k,Value
v)
doOpt :: (Text, Value) -> Parser (Opt -> Opt)
doOpt :: (Text, Value) -> Parser (Opt -> Opt)
doOpt (Text
k,Value
v) = do
  case Text
k of
    Text
"tab-stop" ->
      Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Int -> (Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTabStop :: Int
optTabStop = Int
x })
    Text
"preserve-tabs" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optPreserveTabs :: Bool
optPreserveTabs = Bool
x })
    Text
"standalone" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optStandalone :: Bool
optStandalone = Bool
x })
    Text
"table-of-contents" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTableOfContents :: Bool
optTableOfContents = Bool
x })
    Text
"toc" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTableOfContents :: Bool
optTableOfContents = Bool
x })
    Text
"from" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optFrom :: Maybe Text
optFrom = Maybe Text
x })
    Text
"reader" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optFrom :: Maybe Text
optFrom = Maybe Text
x })
    Text
"to" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTo :: Maybe Text
optTo = Maybe Text
x })
    Text
"writer" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTo :: Maybe Text
optTo = Maybe Text
x })
    Text
"shift-heading-level-by" ->
      Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Int -> (Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optShiftHeadingLevelBy :: Int
optShiftHeadingLevelBy = Int
x })
    Text
"template" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTemplate :: Maybe FilePath
optTemplate = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"variables" ->
      Value -> Parser (Context Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Context Text)
-> (Context Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Context Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optVariables :: Context Text
optVariables =
                                               Context Text
x Context Text -> Context Text -> Context Text
forall a. Semigroup a => a -> a -> a
<> Opt -> Context Text
optVariables Opt
o })
      
      
    Text
"metadata" ->
      Value -> Parser Meta
yamlToMeta Value
v Parser Meta -> (Meta -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Meta
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optMetadata :: Meta
optMetadata = Opt -> Meta
optMetadata Opt
o Meta -> Meta -> Meta
forall a. Semigroup a => a -> a -> a
<> Meta
x })
    Text
"metadata-files" ->
      Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
                        (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optMetadataFiles :: [FilePath]
optMetadataFiles =
                                           Opt -> [FilePath]
optMetadataFiles Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                           (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x })
    Text
"metadata-file" -> 
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optMetadataFiles :: [FilePath]
optMetadataFiles =
                                                Opt -> [FilePath]
optMetadataFiles Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
                        (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optMetadataFiles :: [FilePath]
optMetadataFiles =
                                           Opt -> [FilePath]
optMetadataFiles Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>[Text -> FilePath
unpack Text
x] }))
    Text
"output-file" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optOutputFile :: Maybe FilePath
optOutputFile = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"input-files" ->
      Value -> Parser (Maybe [Text])
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe [Text])
-> (Maybe [Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe [Text]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optInputFiles :: Maybe [FilePath]
optInputFiles =
                                              Opt -> Maybe [FilePath]
optInputFiles Opt
o Maybe [FilePath] -> Maybe [FilePath] -> Maybe [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                ((Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack ([Text] -> [FilePath]) -> Maybe [Text] -> Maybe [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Text]
x) })
    Text
"input-file" -> 
      (Value -> Parser (Maybe [Text])
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe [Text])
-> (Maybe [Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe [Text]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optInputFiles :: Maybe [FilePath]
optInputFiles =
                                                Opt -> Maybe [FilePath]
optInputFiles Opt
o Maybe [FilePath] -> Maybe [FilePath] -> Maybe [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                  ((Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack ([Text] -> [FilePath]) -> Maybe [Text] -> Maybe [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Text]
x) }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optInputFiles :: Maybe [FilePath]
optInputFiles =
                                                Opt -> Maybe [FilePath]
optInputFiles Opt
o Maybe [FilePath] -> Maybe [FilePath] -> Maybe [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                ((\Text
z -> [Text -> FilePath
unpack Text
z]) (Text -> [FilePath]) -> Maybe Text -> Maybe [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x)
                                            }))
    Text
"number-sections" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optNumberSections :: Bool
optNumberSections = Bool
x })
    Text
"number-offset" ->
      Value -> Parser [Int]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Int]
-> ([Int] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Int]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optNumberOffset :: [Int]
optNumberOffset = [Int]
x })
    Text
"section-divs" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSectionDivs :: Bool
optSectionDivs = Bool
x })
    Text
"incremental" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIncremental :: Bool
optIncremental = Bool
x })
    Text
"self-contained" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSelfContained :: Bool
optSelfContained = Bool
x })
    Text
"embed-resources" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optEmbedResources :: Bool
optEmbedResources = Bool
x })
    Text
"html-q-tags" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optHtmlQTags :: Bool
optHtmlQTags = Bool
x })
    Text
"highlight-style" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optHighlightStyle :: Maybe Text
optHighlightStyle = Maybe Text
x })
    Text
"syntax-definition" ->
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
                (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSyntaxDefinitions :: [FilePath]
optSyntaxDefinitions =
                                   Opt -> [FilePath]
optSyntaxDefinitions Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSyntaxDefinitions :: [FilePath]
optSyntaxDefinitions =
                                 Opt -> [FilePath]
optSyntaxDefinitions Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> [Text -> FilePath
unpack Text
x] }))
    Text
"syntax-definitions" ->
      Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSyntaxDefinitions :: [FilePath]
optSyntaxDefinitions =
                                Opt -> [FilePath]
optSyntaxDefinitions Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x })
    Text
"top-level-division" ->
      Value -> Parser TopLevelDivision
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser TopLevelDivision
-> (TopLevelDivision -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \TopLevelDivision
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTopLevelDivision :: TopLevelDivision
optTopLevelDivision = TopLevelDivision
x })
    Text
"html-math-method" ->
      Value -> Parser HTMLMathMethod
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser HTMLMathMethod
-> (HTMLMathMethod -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \HTMLMathMethod
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optHTMLMathMethod :: HTMLMathMethod
optHTMLMathMethod = HTMLMathMethod
x })
    Text
"abbreviations" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optAbbreviations :: Maybe FilePath
optAbbreviations = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"reference-doc" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optReferenceDoc :: Maybe FilePath
optReferenceDoc = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"epub-subdirectory" ->
      Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optEpubSubdirectory :: FilePath
optEpubSubdirectory = Text -> FilePath
unpack Text
x })
    Text
"epub-metadata" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optEpubMetadata :: Maybe FilePath
optEpubMetadata = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"epub-fonts" ->
      Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optEpubFonts :: [FilePath]
optEpubFonts = Opt -> [FilePath]
optEpubFonts Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                               (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x })
    Text
"epub-chapter-level" ->
      Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Int -> (Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSplitLevel :: Int
optSplitLevel = Int
x })
    Text
"split-level" ->
      Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Int -> (Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSplitLevel :: Int
optSplitLevel = Int
x })
    Text
"chunk-template" ->
      Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optChunkTemplate :: Maybe Text
optChunkTemplate = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
x })
    Text
"epub-cover-image" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optEpubCoverImage :: Maybe FilePath
optEpubCoverImage = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"toc-depth" ->
      Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Int -> (Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTOCDepth :: Int
optTOCDepth = Int
x })
    Text
"dump-args" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optDumpArgs :: Bool
optDumpArgs = Bool
x })
    Text
"ignore-args" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIgnoreArgs :: Bool
optIgnoreArgs = Bool
x })
    Text
"verbosity" ->
      Value -> Parser Verbosity
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Verbosity
-> (Verbosity -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Verbosity
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optVerbosity :: Verbosity
optVerbosity = Verbosity
x })
    Text
"trace" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTrace :: Bool
optTrace = Bool
x })
    Text
"log-file" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optLogFile :: Maybe FilePath
optLogFile = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"fail-if-warnings" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optFailIfWarnings :: Bool
optFailIfWarnings = Bool
x })
    Text
"reference-links" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optReferenceLinks :: Bool
optReferenceLinks = Bool
x })
    Text
"reference-location" ->
      Value -> Parser ReferenceLocation
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser ReferenceLocation
-> (ReferenceLocation -> Parser (Opt -> Opt))
-> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ReferenceLocation
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optReferenceLocation :: ReferenceLocation
optReferenceLocation = ReferenceLocation
x })
    Text
"dpi" ->
      Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Int -> (Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optDpi :: Int
optDpi = Int
x })
    Text
"wrap" ->
      Value -> Parser WrapOption
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser WrapOption
-> (WrapOption -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \WrapOption
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optWrap :: WrapOption
optWrap = WrapOption
x })
    Text
"columns" ->
      Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Int -> (Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optColumns :: Int
optColumns = Int
x })
    Text
"filters" ->
      Value -> Parser [Filter]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Filter]
-> ([Filter] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Filter]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optFilters :: [Filter]
optFilters = Opt -> [Filter]
optFilters Opt
o [Filter] -> [Filter] -> [Filter]
forall a. Semigroup a => a -> a -> a
<> [Filter]
x })
    Text
"citeproc" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x ->
        if Bool
x
           then (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optFilters :: [Filter]
optFilters = Filter
CiteprocFilter Filter -> [Filter] -> [Filter]
forall a. a -> [a] -> [a]
: Opt -> [Filter]
optFilters Opt
o })
           else (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Opt -> Opt
forall a. a -> a
id
    Text
"email-obfuscation" ->
      Value -> Parser ObfuscationMethod
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser ObfuscationMethod
-> (ObfuscationMethod -> Parser (Opt -> Opt))
-> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ObfuscationMethod
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optEmailObfuscation :: ObfuscationMethod
optEmailObfuscation = ObfuscationMethod
x })
    Text
"identifier-prefix" ->
      Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIdentifierPrefix :: Text
optIdentifierPrefix = Text
x })
    Text
"indented-code-classes" ->
      Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIndentedCodeClasses :: [Text]
optIndentedCodeClasses = [Text]
x })
    Text
"data-dir" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optDataDir :: Maybe FilePath
optDataDir = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"cite-method" ->
      Value -> Parser CiteMethod
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser CiteMethod
-> (CiteMethod -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CiteMethod
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optCiteMethod :: CiteMethod
optCiteMethod = CiteMethod
x })
    Text
"listings" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optListings :: Bool
optListings = Bool
x })
    Text
"pdf-engine" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optPdfEngine :: Maybe FilePath
optPdfEngine = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"pdf-engine-opts" ->
      Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optPdfEngineOpts :: [FilePath]
optPdfEngineOpts = (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x })
    Text
"pdf-engine-opt" ->
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optPdfEngineOpts :: [FilePath]
optPdfEngineOpts = (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optPdfEngineOpts :: [FilePath]
optPdfEngineOpts = [Text -> FilePath
unpack Text
x] }))
    Text
"slide-level" ->
      Value -> Parser (Maybe Int)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Int)
-> (Maybe Int -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Int
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optSlideLevel :: Maybe Int
optSlideLevel = Maybe Int
x })
    Text
"markdown-headings" ->
      Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o ->
        case Text -> Text
T.toLower Text
x of
          Text
"atx"    -> Opt
o{ optSetextHeaders :: Bool
optSetextHeaders = Bool
False }
          Text
"setext" -> Opt
o{ optSetextHeaders :: Bool
optSetextHeaders = Bool
True }
          Text
_        -> Opt
o)
    Text
"list-tables" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optListTables :: Bool
optListTables = Bool
x })
    Text
"ascii" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optAscii :: Bool
optAscii = Bool
x })
    Text
"default-image-extension" ->
      Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optDefaultImageExtension :: Text
optDefaultImageExtension = Text
x })
    Text
"extract-media" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optExtractMedia :: Maybe FilePath
optExtractMedia = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"track-changes" ->
      Value -> Parser TrackChanges
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser TrackChanges
-> (TrackChanges -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \TrackChanges
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTrackChanges :: TrackChanges
optTrackChanges = TrackChanges
x })
    Text
"file-scope" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optFileScope :: Bool
optFileScope = Bool
x })
    Text
"title-prefix" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optTitlePrefix :: Maybe Text
optTitlePrefix = Maybe Text
x,
                                             optStandalone :: Bool
optStandalone = Bool
True })
    Text
"css" ->
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optCss :: [FilePath]
optCss = Opt -> [FilePath]
optCss Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                 (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optCss :: [FilePath]
optCss = Opt -> [FilePath]
optCss Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                [Text -> FilePath
unpack Text
x] }))
    Text
"bibliography" ->
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o ->
                               Opt
o{ optBibliography :: [FilePath]
optBibliography = Opt -> [FilePath]
optBibliography Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                      (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o ->
                               Opt
o{ optBibliography :: [FilePath]
optBibliography = Opt -> [FilePath]
optBibliography Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                                       [Text -> FilePath
unpack Text
x] }))
    Text
"csl" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optCSL :: Maybe FilePath
optCSL = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"citation-abbreviations" ->
      Value -> Parser (Maybe Text)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Maybe Text)
-> (Maybe Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe Text
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optCitationAbbreviations :: Maybe FilePath
optCitationAbbreviations =
                                                  Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
x })
    Text
"ipynb-output" ->
      Value -> Parser IpynbOutput
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser IpynbOutput
-> (IpynbOutput -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \IpynbOutput
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIpynbOutput :: IpynbOutput
optIpynbOutput = IpynbOutput
x })
    Text
"include-before-body" ->
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIncludeBeforeBody :: [FilePath]
optIncludeBeforeBody =
                                Opt -> [FilePath]
optIncludeBeforeBody Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIncludeBeforeBody :: [FilePath]
optIncludeBeforeBody =
                                Opt -> [FilePath]
optIncludeBeforeBody Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> [Text -> FilePath
unpack Text
x] }))
    Text
"include-after-body" ->
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIncludeAfterBody :: [FilePath]
optIncludeAfterBody =
                                Opt -> [FilePath]
optIncludeAfterBody Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIncludeAfterBody :: [FilePath]
optIncludeAfterBody =
                                Opt -> [FilePath]
optIncludeAfterBody Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> [Text -> FilePath
unpack Text
x] }))
    Text
"include-in-header" ->
      (Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIncludeInHeader :: [FilePath]
optIncludeInHeader =
                                Opt -> [FilePath]
optIncludeInHeader Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x }))
      Parser (Opt -> Opt) -> Parser (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Text -> (Text -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optIncludeInHeader :: [FilePath]
optIncludeInHeader =
                                Opt -> [FilePath]
optIncludeInHeader Opt
o [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> [Text -> FilePath
unpack Text
x] }))
    Text
"resource-path" ->
      Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text]
-> ([Text] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Text]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optResourcePath :: [FilePath]
optResourcePath = (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
unpack [Text]
x [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<>
                                 Opt -> [FilePath]
optResourcePath Opt
o })
    Text
"request-headers" ->
      Value -> Parser [(Text, Text)]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [(Text, Text)]
-> ([(Text, Text)] -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[(Text, Text)]
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optRequestHeaders :: [(Text, Text)]
optRequestHeaders = [(Text, Text)]
x })
    Text
"no-check-certificate" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x ->
             (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optNoCheckCertificate :: Bool
optNoCheckCertificate = Bool
x })
    Text
"eol" ->
      Value -> Parser LineEnding
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser LineEnding
-> (LineEnding -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \LineEnding
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o{ optEol :: LineEnding
optEol = LineEnding
x })
    Text
"strip-comments" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o  { optStripComments :: Bool
optStripComments = Bool
x })
    Text
"sandbox" ->
      Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser Bool -> (Bool -> Parser (Opt -> Opt)) -> Parser (Opt -> Opt)
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> (Opt -> Opt) -> Parser (Opt -> Opt)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (\Opt
o -> Opt
o  { optSandbox :: Bool
optSandbox = Bool
x })
    Text
_ -> FilePath -> Parser (Opt -> Opt)
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser (Opt -> Opt))
-> FilePath -> Parser (Opt -> Opt)
forall a b. (a -> b) -> a -> b
$ FilePath
"Unknown option " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> FilePath
forall a. Show a => a -> FilePath
show Text
k
defaultOpts :: Opt
defaultOpts :: Opt
defaultOpts = Opt
    { optTabStop :: Int
optTabStop               = Int
4
    , optPreserveTabs :: Bool
optPreserveTabs          = Bool
False
    , optStandalone :: Bool
optStandalone            = Bool
False
    , optFrom :: Maybe Text
optFrom                  = Maybe Text
forall a. Maybe a
Nothing
    , optTo :: Maybe Text
optTo                    = Maybe Text
forall a. Maybe a
Nothing
    , optTableOfContents :: Bool
optTableOfContents       = Bool
False
    , optShiftHeadingLevelBy :: Int
optShiftHeadingLevelBy   = Int
0
    , optTemplate :: Maybe FilePath
optTemplate              = Maybe FilePath
forall a. Maybe a
Nothing
    , optVariables :: Context Text
optVariables             = Context Text
forall a. Monoid a => a
mempty
    , optMetadata :: Meta
optMetadata              = Meta
forall a. Monoid a => a
mempty
    , optMetadataFiles :: [FilePath]
optMetadataFiles         = []
    , optOutputFile :: Maybe FilePath
optOutputFile            = Maybe FilePath
forall a. Maybe a
Nothing
    , optInputFiles :: Maybe [FilePath]
optInputFiles            = Maybe [FilePath]
forall a. Maybe a
Nothing
    , optNumberSections :: Bool
optNumberSections        = Bool
False
    , optNumberOffset :: [Int]
optNumberOffset          = [Int
0,Int
0,Int
0,Int
0,Int
0,Int
0]
    , optSectionDivs :: Bool
optSectionDivs           = Bool
False
    , optIncremental :: Bool
optIncremental           = Bool
False
    , optSelfContained :: Bool
optSelfContained         = Bool
False
    , optEmbedResources :: Bool
optEmbedResources        = Bool
False
    , optHtmlQTags :: Bool
optHtmlQTags             = Bool
False
    , optHighlightStyle :: Maybe Text
optHighlightStyle        = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"pygments"
    , optSyntaxDefinitions :: [FilePath]
optSyntaxDefinitions     = []
    , optTopLevelDivision :: TopLevelDivision
optTopLevelDivision      = TopLevelDivision
TopLevelDefault
    , optHTMLMathMethod :: HTMLMathMethod
optHTMLMathMethod        = HTMLMathMethod
PlainMath
    , optAbbreviations :: Maybe FilePath
optAbbreviations         = Maybe FilePath
forall a. Maybe a
Nothing
    , optReferenceDoc :: Maybe FilePath
optReferenceDoc          = Maybe FilePath
forall a. Maybe a
Nothing
    , optSplitLevel :: Int
optSplitLevel            = Int
1
    , optChunkTemplate :: Maybe Text
optChunkTemplate         = Maybe Text
forall a. Maybe a
Nothing
    , optEpubSubdirectory :: FilePath
optEpubSubdirectory      = FilePath
"EPUB"
    , optEpubMetadata :: Maybe FilePath
optEpubMetadata          = Maybe FilePath
forall a. Maybe a
Nothing
    , optEpubFonts :: [FilePath]
optEpubFonts             = []
    , optEpubCoverImage :: Maybe FilePath
optEpubCoverImage        = Maybe FilePath
forall a. Maybe a
Nothing
    , optEpubTitlePage :: Bool
optEpubTitlePage         = Bool
True
    , optTOCDepth :: Int
optTOCDepth              = Int
3
    , optDumpArgs :: Bool
optDumpArgs              = Bool
False
    , optIgnoreArgs :: Bool
optIgnoreArgs            = Bool
False
    , optVerbosity :: Verbosity
optVerbosity             = Verbosity
WARNING
    , optTrace :: Bool
optTrace                 = Bool
False
    , optLogFile :: Maybe FilePath
optLogFile               = Maybe FilePath
forall a. Maybe a
Nothing
    , optFailIfWarnings :: Bool
optFailIfWarnings        = Bool
False
    , optReferenceLinks :: Bool
optReferenceLinks        = Bool
False
    , optReferenceLocation :: ReferenceLocation
optReferenceLocation     = ReferenceLocation
EndOfDocument
    , optDpi :: Int
optDpi                   = Int
96
    , optWrap :: WrapOption
optWrap                  = WrapOption
WrapAuto
    , optColumns :: Int
optColumns               = Int
72
    , optFilters :: [Filter]
optFilters               = []
    , optEmailObfuscation :: ObfuscationMethod
optEmailObfuscation      = ObfuscationMethod
NoObfuscation
    , optIdentifierPrefix :: Text
optIdentifierPrefix      = Text
""
    , optIndentedCodeClasses :: [Text]
optIndentedCodeClasses   = []
    , optDataDir :: Maybe FilePath
optDataDir               = Maybe FilePath
forall a. Maybe a
Nothing
    , optCiteMethod :: CiteMethod
optCiteMethod            = CiteMethod
Citeproc
    , optListings :: Bool
optListings              = Bool
False
    , optPdfEngine :: Maybe FilePath
optPdfEngine             = Maybe FilePath
forall a. Maybe a
Nothing
    , optPdfEngineOpts :: [FilePath]
optPdfEngineOpts         = []
    , optSlideLevel :: Maybe Int
optSlideLevel            = Maybe Int
forall a. Maybe a
Nothing
    , optSetextHeaders :: Bool
optSetextHeaders         = Bool
False
    , optListTables :: Bool
optListTables            = Bool
False
    , optAscii :: Bool
optAscii                 = Bool
False
    , optDefaultImageExtension :: Text
optDefaultImageExtension = Text
""
    , optExtractMedia :: Maybe FilePath
optExtractMedia          = Maybe FilePath
forall a. Maybe a
Nothing
    , optTrackChanges :: TrackChanges
optTrackChanges          = TrackChanges
AcceptChanges
    , optFileScope :: Bool
optFileScope             = Bool
False
    , optTitlePrefix :: Maybe Text
optTitlePrefix           = Maybe Text
forall a. Maybe a
Nothing
    , optCss :: [FilePath]
optCss                   = []
    , optIpynbOutput :: IpynbOutput
optIpynbOutput           = IpynbOutput
IpynbOutputBest
    , optIncludeBeforeBody :: [FilePath]
optIncludeBeforeBody     = []
    , optIncludeAfterBody :: [FilePath]
optIncludeAfterBody      = []
    , optIncludeInHeader :: [FilePath]
optIncludeInHeader       = []
    , optResourcePath :: [FilePath]
optResourcePath          = [FilePath
"."]
    , optRequestHeaders :: [(Text, Text)]
optRequestHeaders        = []
    , optNoCheckCertificate :: Bool
optNoCheckCertificate    = Bool
False
    , optEol :: LineEnding
optEol                   = LineEnding
Native
    , optStripComments :: Bool
optStripComments         = Bool
False
    , optCSL :: Maybe FilePath
optCSL                   = Maybe FilePath
forall a. Maybe a
Nothing
    , optBibliography :: [FilePath]
optBibliography          = []
    , optCitationAbbreviations :: Maybe FilePath
optCitationAbbreviations = Maybe FilePath
forall a. Maybe a
Nothing
    , optSandbox :: Bool
optSandbox               = Bool
False
    }
yamlToMeta :: Value -> Parser Meta
yamlToMeta :: Value -> Parser Meta
yamlToMeta (Object Object
o) =
  (PandocError -> Parser Meta)
-> (Meta -> Parser Meta) -> Either PandocError Meta -> Parser Meta
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (FilePath -> Parser Meta
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser Meta)
-> (PandocError -> FilePath) -> PandocError -> Parser Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PandocError -> FilePath
forall a. Show a => a -> FilePath
show) Meta -> Parser Meta
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PandocError Meta -> Parser Meta)
-> Either PandocError Meta -> Parser Meta
forall a b. (a -> b) -> a -> b
$ ParsecT
  Sources
  ParserState
  PandocPure
  (Future ParserState (Map Text MetaValue))
-> Either PandocError Meta
forall {b}.
Default b =>
ParsecT
  Sources ParserState PandocPure (Future b (Map Text MetaValue))
-> Either PandocError Meta
runEverything (ParsecT
  Sources ParserState PandocPure (Future ParserState MetaValue)
-> Object
-> ParsecT
     Sources
     ParserState
     PandocPure
     (Future ParserState (Map Text MetaValue))
forall (m :: * -> *) st.
(PandocMonad m, HasLastStrPosition st) =>
ParsecT Sources st m (Future st MetaValue)
-> Object -> ParsecT Sources st m (Future st (Map Text MetaValue))
yamlMap ParsecT
  Sources ParserState PandocPure (Future ParserState MetaValue)
forall {st}.
ParsecT Sources st PandocPure (Future ParserState MetaValue)
pMetaString Object
o)
 where
  pMetaString :: ParsecT Sources st PandocPure (Future ParserState MetaValue)
pMetaString = MetaValue -> Future ParserState MetaValue
forall a. a -> Future ParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MetaValue -> Future ParserState MetaValue)
-> (Text -> MetaValue) -> Text -> Future ParserState MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> MetaValue
MetaString (Text -> Future ParserState MetaValue)
-> ParsecT Sources st PandocPure Text
-> ParsecT Sources st PandocPure (Future ParserState MetaValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources st PandocPure Char
-> ParsecT Sources st PandocPure Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
P.manyChar ParsecT Sources st PandocPure Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
P.anyChar
  runEverything :: ParsecT
  Sources ParserState PandocPure (Future b (Map Text MetaValue))
-> Either PandocError Meta
runEverything ParsecT
  Sources ParserState PandocPure (Future b (Map Text MetaValue))
p =
      PandocPure (Either PandocError (Future b (Map Text MetaValue)))
-> Either
     PandocError (Either PandocError (Future b (Map Text MetaValue)))
forall a. PandocPure a -> Either PandocError a
runPure (ParsecT
  Sources ParserState PandocPure (Future b (Map Text MetaValue))
-> ParserState
-> Text
-> PandocPure (Either PandocError (Future b (Map Text MetaValue)))
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
P.readWithM ParsecT
  Sources ParserState PandocPure (Future b (Map Text MetaValue))
p (ParserState
forall a. Default a => a
def :: P.ParserState) (Text
"" :: Text))
      Either
  PandocError (Either PandocError (Future b (Map Text MetaValue)))
-> (Either PandocError (Future b (Map Text MetaValue))
    -> Either PandocError Meta)
-> Either PandocError Meta
forall a b.
Either PandocError a
-> (a -> Either PandocError b) -> Either PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Future b (Map Text MetaValue) -> Meta)
-> Either PandocError (Future b (Map Text MetaValue))
-> Either PandocError Meta
forall a b.
(a -> b) -> Either PandocError a -> Either PandocError b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Map Text MetaValue -> Meta
Meta (Map Text MetaValue -> Meta)
-> (Future b (Map Text MetaValue) -> Map Text MetaValue)
-> Future b (Map Text MetaValue)
-> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Future b (Map Text MetaValue) -> b -> Map Text MetaValue)
-> b -> Future b (Map Text MetaValue) -> Map Text MetaValue
forall a b c. (a -> b -> c) -> b -> a -> c
flip Future b (Map Text MetaValue) -> b -> Map Text MetaValue
forall s a. Future s a -> s -> a
P.runF b
forall a. Default a => a
def)
yamlToMeta Value
_ = Meta -> Parser Meta
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Meta
forall a. Monoid a => a
mempty
applyDefaults :: (PandocMonad m, MonadIO m)
              => Opt
              -> FilePath
              -> StateT DefaultsState m Opt
applyDefaults :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Opt -> FilePath -> StateT DefaultsState m Opt
applyDefaults Opt
opt FilePath
file = do
  Verbosity -> StateT DefaultsState m ()
forall (m :: * -> *). PandocMonad m => Verbosity -> m ()
setVerbosity (Verbosity -> StateT DefaultsState m ())
-> Verbosity -> StateT DefaultsState m ()
forall a b. (a -> b) -> a -> b
$ Opt -> Verbosity
optVerbosity Opt
opt
  (DefaultsState -> DefaultsState) -> StateT DefaultsState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DefaultsState -> DefaultsState) -> StateT DefaultsState m ())
-> (DefaultsState -> DefaultsState) -> StateT DefaultsState m ()
forall a b. (a -> b) -> a -> b
$ \DefaultsState
defsState -> DefaultsState
defsState{ curDefaults :: Maybe FilePath
curDefaults = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
file }
  ByteString
inp <- FilePath -> StateT DefaultsState m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readFileStrict FilePath
file
  case ByteString
-> Either ParseException (Opt -> StateT DefaultsState m Opt)
forall a. FromJSON a => ByteString -> Either ParseException a
decodeEither' ([ByteString] -> ByteString
B8.unlines ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Bool) -> [ByteString] -> [ByteString]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
/= ByteString
"...") ([ByteString] -> [ByteString])
-> (ByteString -> [ByteString]) -> ByteString -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
B8.lines (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
inp) of
      Right Opt -> StateT DefaultsState m Opt
f -> Opt -> StateT DefaultsState m Opt
f Opt
opt
      Left ParseException
err'  -> PandocError -> StateT DefaultsState m Opt
forall a. PandocError -> StateT DefaultsState m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> StateT DefaultsState m Opt)
-> PandocError -> StateT DefaultsState m Opt
forall a b. (a -> b) -> a -> b
$
         Text -> PandocError
PandocParseError
             (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ ParseException -> FilePath
Data.Yaml.prettyPrintParseException ParseException
err'
fullDefaultsPath :: (PandocMonad m, MonadIO m)
                 => Maybe FilePath
                 -> FilePath
                 -> m FilePath
fullDefaultsPath :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Maybe FilePath -> FilePath -> m FilePath
fullDefaultsPath Maybe FilePath
dataDir FilePath
file = do
  let fp :: FilePath
fp = if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (ShowS
takeExtension FilePath
file)
              then FilePath -> ShowS
addExtension FilePath
file FilePath
"yaml"
              else FilePath
file
  FilePath
defaultDataDir <- IO FilePath -> m FilePath
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO FilePath
defaultUserDataDir
  let defaultFp :: FilePath
defaultFp = FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
defaultDataDir Maybe FilePath
dataDir FilePath -> ShowS
</> FilePath
"defaults" FilePath -> ShowS
</> FilePath
fp
  Bool
fpExists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists FilePath
fp
  if Bool
fpExists
     then FilePath -> m FilePath
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp
     else do
       Bool
defaultFpExists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists FilePath
defaultFp
       if Bool
defaultFpExists
          then FilePath -> m FilePath
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
defaultFp
          else FilePath -> m FilePath
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp
expand :: Ord a => [[a]] -> [a] -> a -> [[a]]
expand :: forall a. Ord a => [[a]] -> [a] -> a -> [[a]]
expand [] [a]
ns a
n = (a -> [a]) -> [a] -> [[a]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a
x -> a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a
n]) [a]
ns
expand [[a]]
ps [a]
ns a
n = ([a] -> [[a]]) -> [[a]] -> [[a]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (a -> [a] -> [a] -> [[a]]
forall {a}. Eq a => a -> [a] -> [a] -> [[a]]
ext a
n [a]
ns) [[a]]
ps
  where
    ext :: a -> [a] -> [a] -> [[a]]
ext a
x [a]
xs [a]
p = case [a]
p of
      (a
l : [a]
_) | a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
l -> (a -> [a]) -> [a] -> [[a]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
p) [a]
xs
      [a]
_ -> [[a]
p]
cyclic :: Ord a => [[a]] -> Bool
cyclic :: forall a. Ord a => [[a]] -> Bool
cyclic = ([a] -> Bool) -> [[a]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any [a] -> Bool
forall {a}. Ord a => [a] -> Bool
hasDuplicate
  where
    hasDuplicate :: [a] -> Bool
hasDuplicate [a]
xs = [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> [a]
forall a. Ord a => [a] -> [a]
nubOrd [a]
xs) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs