module Text.Pandoc.Options ( module Text.Pandoc.Extensions
, ReaderOptions(..)
, HTMLMathMethod (..)
, CiteMethod (..)
, ObfuscationMethod (..)
, HTMLSlideVariant (..)
, EPUBVersion (..)
, WrapOption (..)
, TopLevelDivision (..)
, WriterOptions (..)
, TrackChanges (..)
, ReferenceLocation (..)
, def
, isEnabled
) where
import Data.Aeson (FromJSON (..), ToJSON (..), defaultOptions,
genericToEncoding)
import Data.Data (Data)
import Data.Default
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Skylighting (SyntaxMap, defaultSyntaxMap)
import Text.Pandoc.Extensions
import Text.Pandoc.Highlighting (Style, pygments)
data ReaderOptions = ReaderOptions{
readerExtensions :: Extensions
, readerStandalone :: Bool
, readerColumns :: Int
, readerTabStop :: Int
, readerIndentedCodeClasses :: [String]
, readerAbbreviations :: Set.Set String
, readerDefaultImageExtension :: String
, readerTrackChanges :: TrackChanges
, readerStripComments :: Bool
} deriving (Show, Read, Data, Typeable, Generic)
instance ToJSON ReaderOptions where
toEncoding = genericToEncoding defaultOptions
instance FromJSON ReaderOptions
instance Default ReaderOptions
where def = ReaderOptions{
readerExtensions = emptyExtensions
, readerStandalone = False
, readerColumns = 80
, readerTabStop = 4
, readerIndentedCodeClasses = []
, readerAbbreviations = defaultAbbrevs
, readerDefaultImageExtension = ""
, readerTrackChanges = AcceptChanges
, readerStripComments = False
}
defaultAbbrevs :: Set.Set String
defaultAbbrevs = Set.fromList
[ "Mr.", "Mrs.", "Ms.", "Capt.", "Dr.", "Prof.",
"Gen.", "Gov.", "e.g.", "i.e.", "Sgt.", "St.",
"vol.", "vs.", "Sen.", "Rep.", "Pres.", "Hon.",
"Rev.", "Ph.D.", "M.D.", "M.A.", "p.", "pp.",
"ch.", "sec.", "cf.", "cp."]
data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Generic)
data HTMLMathMethod = PlainMath
| LaTeXMathML (Maybe String)
| JsMath (Maybe String)
| GladTeX
| WebTeX String
| MathML
| MathJax String
| KaTeX String
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON HTMLMathMethod where
toEncoding = genericToEncoding defaultOptions
instance FromJSON HTMLMathMethod
data CiteMethod = Citeproc
| Natbib
| Biblatex
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON CiteMethod where
toEncoding = genericToEncoding defaultOptions
instance FromJSON CiteMethod
data ObfuscationMethod = NoObfuscation
| ReferenceObfuscation
| JavascriptObfuscation
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON ObfuscationMethod where
toEncoding = genericToEncoding defaultOptions
instance FromJSON ObfuscationMethod
data HTMLSlideVariant = S5Slides
| SlidySlides
| SlideousSlides
| DZSlides
| RevealJsSlides
| NoSlides
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON HTMLSlideVariant where
toEncoding = genericToEncoding defaultOptions
instance FromJSON HTMLSlideVariant
data TrackChanges = AcceptChanges
| RejectChanges
| AllChanges
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON TrackChanges where
toEncoding = genericToEncoding defaultOptions
instance FromJSON TrackChanges
data WrapOption = WrapAuto
| WrapNone
| WrapPreserve
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON WrapOption where
toEncoding = genericToEncoding defaultOptions
instance FromJSON WrapOption
data TopLevelDivision = TopLevelPart
| TopLevelChapter
| TopLevelSection
| TopLevelDefault
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON TopLevelDivision where
toEncoding = genericToEncoding defaultOptions
instance FromJSON TopLevelDivision
data ReferenceLocation = EndOfBlock
| EndOfSection
| EndOfDocument
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON ReferenceLocation where
toEncoding = genericToEncoding defaultOptions
instance FromJSON ReferenceLocation
data WriterOptions = WriterOptions
{ writerTemplate :: Maybe String
, writerVariables :: [(String, String)]
, writerTabStop :: Int
, writerTableOfContents :: Bool
, writerIncremental :: Bool
, writerHTMLMathMethod :: HTMLMathMethod
, writerNumberSections :: Bool
, writerNumberOffset :: [Int]
, writerSectionDivs :: Bool
, writerExtensions :: Extensions
, writerReferenceLinks :: Bool
, writerDpi :: Int
, writerWrapText :: WrapOption
, writerColumns :: Int
, writerEmailObfuscation :: ObfuscationMethod
, writerIdentifierPrefix :: String
, writerCiteMethod :: CiteMethod
, writerHtmlQTags :: Bool
, writerSlideLevel :: Maybe Int
, writerTopLevelDivision :: TopLevelDivision
, writerListings :: Bool
, writerHighlightStyle :: Maybe Style
, writerSetextHeaders :: Bool
, writerEpubSubdirectory :: String
, writerEpubMetadata :: Maybe String
, writerEpubFonts :: [FilePath]
, writerEpubChapterLevel :: Int
, writerTOCDepth :: Int
, writerReferenceDoc :: Maybe FilePath
, writerReferenceLocation :: ReferenceLocation
, writerSyntaxMap :: SyntaxMap
} deriving (Show, Data, Typeable, Generic)
instance Default WriterOptions where
def = WriterOptions { writerTemplate = Nothing
, writerVariables = []
, writerTabStop = 4
, writerTableOfContents = False
, writerIncremental = False
, writerHTMLMathMethod = PlainMath
, writerNumberSections = False
, writerNumberOffset = [0,0,0,0,0,0]
, writerSectionDivs = False
, writerExtensions = emptyExtensions
, writerReferenceLinks = False
, writerDpi = 96
, writerWrapText = WrapAuto
, writerColumns = 72
, writerEmailObfuscation = NoObfuscation
, writerIdentifierPrefix = ""
, writerCiteMethod = Citeproc
, writerHtmlQTags = False
, writerSlideLevel = Nothing
, writerTopLevelDivision = TopLevelDefault
, writerListings = False
, writerHighlightStyle = Just pygments
, writerSetextHeaders = True
, writerEpubSubdirectory = "EPUB"
, writerEpubMetadata = Nothing
, writerEpubFonts = []
, writerEpubChapterLevel = 1
, writerTOCDepth = 3
, writerReferenceDoc = Nothing
, writerReferenceLocation = EndOfDocument
, writerSyntaxMap = defaultSyntaxMap
}
isEnabled :: Extension -> WriterOptions -> Bool
isEnabled ext opts = ext `extensionEnabled` writerExtensions opts