{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
#ifdef DERIVE_JSON_VIA_TH
{-# LANGUAGE TemplateHaskell #-}
#endif
module Text.Pandoc.App.Opt (
Opt(..)
, LineEnding (..)
, defaultOpts
) where
import Prelude
import GHC.Generics
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Highlighting (Style, pygments)
import Text.Pandoc.Logging (Verbosity (WARNING))
import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
TrackChanges (AcceptChanges),
WrapOption (WrapAuto), HTMLMathMethod (PlainMath),
ReferenceLocation (EndOfDocument),
ObfuscationMethod (NoObfuscation),
CiteMethod (Citeproc))
#ifdef DERIVE_JSON_VIA_TH
import Data.Aeson.TH (deriveJSON, defaultOptions)
#else
import Data.Aeson (FromJSON (..), ToJSON (..),
defaultOptions, genericToEncoding)
#endif
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
data Opt = Opt
{ optTabStop :: Int
, optPreserveTabs :: Bool
, optStandalone :: Bool
, optReader :: Maybe String
, optWriter :: Maybe String
, optTableOfContents :: Bool
, optBaseHeaderLevel :: Int
, optTemplate :: Maybe FilePath
, optVariables :: [(String,String)]
, optMetadata :: [(String, String)]
, optMetadataFile :: Maybe FilePath
, optOutputFile :: Maybe FilePath
, optInputFiles :: [FilePath]
, optNumberSections :: Bool
, optNumberOffset :: [Int]
, optSectionDivs :: Bool
, optIncremental :: Bool
, optSelfContained :: Bool
, optHtmlQTags :: Bool
, optHighlightStyle :: Maybe Style
, optSyntaxDefinitions :: [FilePath]
, optTopLevelDivision :: TopLevelDivision
, optHTMLMathMethod :: HTMLMathMethod
, optAbbreviations :: Maybe FilePath
, optReferenceDoc :: Maybe FilePath
, optEpubSubdirectory :: String
, optEpubMetadata :: Maybe FilePath
, optEpubFonts :: [FilePath]
, optEpubChapterLevel :: Int
, optEpubCoverImage :: Maybe FilePath
, optTOCDepth :: Int
, optDumpArgs :: Bool
, optIgnoreArgs :: Bool
, optVerbosity :: Verbosity
, optTrace :: Bool
, optLogFile :: Maybe FilePath
, optFailIfWarnings :: Bool
, optReferenceLinks :: Bool
, optReferenceLocation :: ReferenceLocation
, optDpi :: Int
, optWrapText :: WrapOption
, optColumns :: Int
, optFilters :: [Filter]
, optEmailObfuscation :: ObfuscationMethod
, optIdentifierPrefix :: String
, optStripEmptyParagraphs :: Bool
, optIndentedCodeClasses :: [String]
, optDataDir :: Maybe FilePath
, optCiteMethod :: CiteMethod
, optListings :: Bool
, optPdfEngine :: Maybe String
, optPdfEngineArgs :: [String]
, optSlideLevel :: Maybe Int
, optSetextHeaders :: Bool
, optAscii :: Bool
, optDefaultImageExtension :: String
, optExtractMedia :: Maybe FilePath
, optTrackChanges :: TrackChanges
, optFileScope :: Bool
, optTitlePrefix :: Maybe String
, optCss :: [FilePath]
, optIpynbOutput :: String
, optIncludeBeforeBody :: [FilePath]
, optIncludeAfterBody :: [FilePath]
, optIncludeInHeader :: [FilePath]
, optResourcePath :: [FilePath]
, optRequestHeaders :: [(String, String)]
, optEol :: LineEnding
, optStripComments :: Bool
} deriving (Generic, Show)
defaultOpts :: Opt
defaultOpts = Opt
{ optTabStop = 4
, optPreserveTabs = False
, optStandalone = False
, optReader = Nothing
, optWriter = Nothing
, optTableOfContents = False
, optBaseHeaderLevel = 1
, optTemplate = Nothing
, optVariables = []
, optMetadata = []
, optMetadataFile = Nothing
, optOutputFile = Nothing
, optInputFiles = []
, optNumberSections = False
, optNumberOffset = [0,0,0,0,0,0]
, optSectionDivs = False
, optIncremental = False
, optSelfContained = False
, optHtmlQTags = False
, optHighlightStyle = Just pygments
, optSyntaxDefinitions = []
, optTopLevelDivision = TopLevelDefault
, optHTMLMathMethod = PlainMath
, optAbbreviations = Nothing
, optReferenceDoc = Nothing
, optEpubSubdirectory = "EPUB"
, optEpubMetadata = Nothing
, optEpubFonts = []
, optEpubChapterLevel = 1
, optEpubCoverImage = Nothing
, optTOCDepth = 3
, optDumpArgs = False
, optIgnoreArgs = False
, optVerbosity = WARNING
, optTrace = False
, optLogFile = Nothing
, optFailIfWarnings = False
, optReferenceLinks = False
, optReferenceLocation = EndOfDocument
, optDpi = 96
, optWrapText = WrapAuto
, optColumns = 72
, optFilters = []
, optEmailObfuscation = NoObfuscation
, optIdentifierPrefix = ""
, optStripEmptyParagraphs = False
, optIndentedCodeClasses = []
, optDataDir = Nothing
, optCiteMethod = Citeproc
, optListings = False
, optPdfEngine = Nothing
, optPdfEngineArgs = []
, optSlideLevel = Nothing
, optSetextHeaders = True
, optAscii = False
, optDefaultImageExtension = ""
, optExtractMedia = Nothing
, optTrackChanges = AcceptChanges
, optFileScope = False
, optTitlePrefix = Nothing
, optCss = []
, optIpynbOutput = "best"
, optIncludeBeforeBody = []
, optIncludeAfterBody = []
, optIncludeInHeader = []
, optResourcePath = ["."]
, optRequestHeaders = []
, optEol = Native
, optStripComments = False
}
#ifdef DERIVE_JSON_VIA_TH
$(deriveJSON defaultOptions ''LineEnding)
$(deriveJSON defaultOptions ''Opt)
#else
instance ToJSON LineEnding where
toEncoding = genericToEncoding defaultOptions
instance FromJSON LineEnding
instance ToJSON Opt where
toEncoding = genericToEncoding defaultOptions
instance FromJSON Opt
#endif