1{-# LANGUAGE CPP                #-}
2{-# LANGUAGE DeriveDataTypeable #-}
3{-# LANGUAGE DeriveGeneric      #-}
4{-# LANGUAGE LambdaCase         #-}
5{-# LANGUAGE OverloadedStrings  #-}
6{-# LANGUAGE TemplateHaskell    #-}
7{- |
8   Module      : Text.Pandoc.Options
9   Copyright   : Copyright (C) 2012-2021 John MacFarlane
10   License     : GNU GPL, version 2 or above
11
12   Maintainer  : John MacFarlane <jgm@berkeley.edu>
13   Stability   : alpha
14   Portability : portable
15
16Data structures and functions for representing parser and writer
17options.
18-}
19module Text.Pandoc.Options ( module Text.Pandoc.Extensions
20                           , ReaderOptions(..)
21                           , HTMLMathMethod (..)
22                           , CiteMethod (..)
23                           , ObfuscationMethod (..)
24                           , HTMLSlideVariant (..)
25                           , EPUBVersion (..)
26                           , WrapOption (..)
27                           , TopLevelDivision (..)
28                           , WriterOptions (..)
29                           , TrackChanges (..)
30                           , ReferenceLocation (..)
31                           , def
32                           , isEnabled
33                           , defaultMathJaxURL
34                           , defaultKaTeXURL
35                           ) where
36import Control.Applicative ((<|>))
37import Data.Char (toLower)
38import Data.Maybe (fromMaybe)
39import Data.Data (Data)
40import Data.Default
41import Data.Text (Text)
42import qualified Data.Set as Set
43import Data.Typeable (Typeable)
44import GHC.Generics (Generic)
45import Skylighting (SyntaxMap, defaultSyntaxMap)
46import Text.DocTemplates (Context(..), Template)
47import Text.Pandoc.Extensions
48import Text.Pandoc.Highlighting (Style, pygments)
49import Text.Pandoc.Shared (camelCaseStrToHyphenated)
50import Data.Aeson.TH (deriveJSON, defaultOptions, Options(..),
51                      SumEncoding(..))
52import Data.YAML
53
54class HasSyntaxExtensions a where
55  getExtensions :: a -> Extensions
56
57data ReaderOptions = ReaderOptions{
58         readerExtensions            :: Extensions  -- ^ Syntax extensions
59       , readerStandalone            :: Bool -- ^ Standalone document with header
60       , readerColumns               :: Int  -- ^ Number of columns in terminal
61       , readerTabStop               :: Int  -- ^ Tab stop
62       , readerIndentedCodeClasses   :: [Text] -- ^ Default classes for
63                                       -- indented code blocks
64       , readerAbbreviations         :: Set.Set Text -- ^ Strings to treat as abbreviations
65       , readerDefaultImageExtension :: Text -- ^ Default extension for images
66       , readerTrackChanges          :: TrackChanges -- ^ Track changes setting for docx
67       , readerStripComments         :: Bool -- ^ Strip HTML comments instead of parsing as raw HTML
68                                             -- (only implemented in commonmark)
69} deriving (Show, Read, Data, Typeable, Generic)
70
71instance HasSyntaxExtensions ReaderOptions where
72  getExtensions opts = readerExtensions opts
73
74instance Default ReaderOptions
75  where def = ReaderOptions{
76                 readerExtensions            = emptyExtensions
77               , readerStandalone            = False
78               , readerColumns               = 80
79               , readerTabStop               = 4
80               , readerIndentedCodeClasses   = []
81               , readerAbbreviations         = defaultAbbrevs
82               , readerDefaultImageExtension = ""
83               , readerTrackChanges          = AcceptChanges
84               , readerStripComments         = False
85               }
86
87defaultAbbrevs :: Set.Set Text
88defaultAbbrevs = Set.fromList
89                 [ "Mr.", "Mrs.", "Ms.", "Capt.", "Dr.", "Prof.",
90                   "Gen.", "Gov.", "e.g.", "i.e.", "Sgt.", "St.",
91                   "vol.", "vs.", "Sen.", "Rep.", "Pres.", "Hon.",
92                   "Rev.", "Ph.D.", "M.D.", "M.A.", "p.", "pp.",
93                   "ch.", "sec.", "cf.", "cp."]
94
95--
96-- Writer options
97--
98
99data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Generic)
100
101data HTMLMathMethod = PlainMath
102                    | WebTeX Text               -- url of TeX->image script.
103                    | GladTeX
104                    | MathML
105                    | MathJax Text              -- url of MathJax.js
106                    | KaTeX Text                -- url of KaTeX files
107                    deriving (Show, Read, Eq, Data, Typeable, Generic)
108
109instance FromYAML HTMLMathMethod where
110   parseYAML node =
111     (withMap "HTMLMathMethod" $ \m -> do
112        method <- m .: "method"
113        mburl <- m .:? "url"
114        case method :: Text of
115          "plain" -> return PlainMath
116          "webtex" -> return $ WebTeX $ fromMaybe "" mburl
117          "gladtex" -> return GladTeX
118          "mathml" -> return MathML
119          "mathjax" -> return $ MathJax $
120                         fromMaybe defaultMathJaxURL mburl
121          "katex" -> return $ KaTeX $
122                         fromMaybe defaultKaTeXURL mburl
123          _ -> fail $ "Unknown HTML math method " ++ show method) node
124       <|> (withStr "HTMLMathMethod" $ \method ->
125             case method of
126               "plain" -> return PlainMath
127               "webtex" -> return $ WebTeX ""
128               "gladtex" -> return GladTeX
129               "mathml" -> return MathML
130               "mathjax" -> return $ MathJax defaultMathJaxURL
131               "katex" -> return $ KaTeX defaultKaTeXURL
132               _  -> fail $ "Unknown HTML math method " ++ show method) node
133
134data CiteMethod = Citeproc                        -- use citeproc to render them
135                  | Natbib                        -- output natbib cite commands
136                  | Biblatex                      -- output biblatex cite commands
137                deriving (Show, Read, Eq, Data, Typeable, Generic)
138
139instance FromYAML CiteMethod where
140  parseYAML = withStr "Citeproc" $ \t ->
141    case t of
142      "citeproc" -> return Citeproc
143      "natbib"   -> return Natbib
144      "biblatex" -> return Biblatex
145      _          -> fail $ "Unknown citation method " ++ show t
146
147-- | Methods for obfuscating email addresses in HTML.
148data ObfuscationMethod = NoObfuscation
149                       | ReferenceObfuscation
150                       | JavascriptObfuscation
151                       deriving (Show, Read, Eq, Data, Typeable, Generic)
152
153instance FromYAML ObfuscationMethod where
154  parseYAML = withStr "Citeproc" $ \t ->
155    case t of
156      "none"       -> return NoObfuscation
157      "references" -> return ReferenceObfuscation
158      "javascript" -> return JavascriptObfuscation
159      _            -> fail $ "Unknown obfuscation method " ++ show t
160
161-- | Varieties of HTML slide shows.
162data HTMLSlideVariant = S5Slides
163                      | SlidySlides
164                      | SlideousSlides
165                      | DZSlides
166                      | RevealJsSlides
167                      | NoSlides
168                      deriving (Show, Read, Eq, Data, Typeable, Generic)
169
170-- | Options for accepting or rejecting MS Word track-changes.
171data TrackChanges = AcceptChanges
172                  | RejectChanges
173                  | AllChanges
174                  deriving (Show, Read, Eq, Data, Typeable, Generic)
175
176instance FromYAML TrackChanges where
177  parseYAML = withStr "TrackChanges" $ \t ->
178    case t of
179      "accept"     -> return AcceptChanges
180      "reject"     -> return RejectChanges
181      "all"        -> return AllChanges
182      _            -> fail $ "Unknown track changes method " ++ show t
183
184-- | Options for wrapping text in the output.
185data WrapOption = WrapAuto        -- ^ Automatically wrap to width
186                | WrapNone        -- ^ No non-semantic newlines
187                | WrapPreserve    -- ^ Preserve wrapping of input source
188                deriving (Show, Read, Eq, Data, Typeable, Generic)
189
190instance FromYAML WrapOption where
191  parseYAML = withStr "WrapOption" $ \t ->
192    case t of
193      "auto"     -> return WrapAuto
194      "none"     -> return WrapNone
195      "preserve" -> return WrapPreserve
196      _          -> fail $ "Unknown wrap method " ++ show t
197
198
199-- | Options defining the type of top-level headers.
200data TopLevelDivision = TopLevelPart      -- ^ Top-level headers become parts
201                      | TopLevelChapter   -- ^ Top-level headers become chapters
202                      | TopLevelSection   -- ^ Top-level headers become sections
203                      | TopLevelDefault   -- ^ Top-level type is determined via
204                                          --   heuristics
205                      deriving (Show, Read, Eq, Data, Typeable, Generic)
206
207instance FromYAML TopLevelDivision where
208  parseYAML = withStr "TopLevelDivision" $ \t ->
209    case t of
210      "part"     -> return TopLevelPart
211      "chapter"  -> return TopLevelChapter
212      "section"  -> return TopLevelSection
213      "default"  -> return TopLevelDefault
214      _          -> fail $ "Unknown top level division " ++ show t
215
216
217-- | Locations for footnotes and references in markdown output
218data ReferenceLocation = EndOfBlock    -- ^ End of block
219                       | EndOfSection  -- ^ prior to next section header (or end of document)
220                       | EndOfDocument -- ^ at end of document
221                       deriving (Show, Read, Eq, Data, Typeable, Generic)
222
223instance FromYAML ReferenceLocation where
224  parseYAML = withStr "ReferenceLocation" $ \t ->
225    case t of
226      "block"    -> return EndOfBlock
227      "section"  -> return EndOfSection
228      "document" -> return EndOfDocument
229      _          -> fail $ "Unknown reference location " ++ show t
230
231
232-- | Options for writers
233data WriterOptions = WriterOptions
234  { writerTemplate          :: Maybe (Template Text) -- ^ Template to use
235  , writerVariables         :: Context Text -- ^ Variables to set in template
236  , writerTabStop           :: Int    -- ^ Tabstop for conversion btw spaces and tabs
237  , writerTableOfContents   :: Bool   -- ^ Include table of contents
238  , writerIncremental       :: Bool   -- ^ True if lists should be incremental
239  , writerHTMLMathMethod    :: HTMLMathMethod  -- ^ How to print math in HTML
240  , writerNumberSections    :: Bool   -- ^ Number sections in LaTeX
241  , writerNumberOffset      :: [Int]  -- ^ Starting number for section, subsection, ...
242  , writerSectionDivs       :: Bool   -- ^ Put sections in div tags in HTML
243  , writerExtensions        :: Extensions -- ^ Markdown extensions that can be used
244  , writerReferenceLinks    :: Bool   -- ^ Use reference links in writing markdown, rst
245  , writerDpi               :: Int    -- ^ Dpi for pixel to\/from inch\/cm conversions
246  , writerWrapText          :: WrapOption  -- ^ Option for wrapping text
247  , writerColumns           :: Int    -- ^ Characters in a line (for text wrapping)
248  , writerEmailObfuscation  :: ObfuscationMethod -- ^ How to obfuscate emails
249  , writerIdentifierPrefix  :: Text -- ^ Prefix for section & note ids in HTML
250                                     -- and for footnote marks in markdown
251  , writerCiteMethod        :: CiteMethod -- ^ How to print cites
252  , writerHtmlQTags         :: Bool       -- ^ Use @<q>@ tags for quotes in HTML
253  , writerSlideLevel        :: Maybe Int  -- ^ Force header level of slides
254  , writerTopLevelDivision  :: TopLevelDivision -- ^ Type of top-level divisions
255  , writerListings          :: Bool       -- ^ Use listings package for code
256  , writerHighlightStyle    :: Maybe Style  -- ^ Style to use for highlighting
257                                           -- (Nothing = no highlighting)
258  , writerSetextHeaders     :: Bool       -- ^ Use setext headers for levels 1-2 in markdown
259  , writerEpubSubdirectory  :: Text       -- ^ Subdir for epub in OCF
260  , writerEpubMetadata      :: Maybe Text -- ^ Metadata to include in EPUB
261  , writerEpubFonts         :: [FilePath] -- ^ Paths to fonts to embed
262  , writerEpubChapterLevel  :: Int            -- ^ Header level for chapters (separate files)
263  , writerTOCDepth          :: Int            -- ^ Number of levels to include in TOC
264  , writerReferenceDoc      :: Maybe FilePath -- ^ Path to reference document if specified
265  , writerReferenceLocation :: ReferenceLocation    -- ^ Location of footnotes and references for writing markdown
266  , writerSyntaxMap         :: SyntaxMap
267  , writerPreferAscii       :: Bool           -- ^ Prefer ASCII representations of characters when possible
268  } deriving (Show, Data, Typeable, Generic)
269
270instance Default WriterOptions where
271  def = WriterOptions { writerTemplate         = Nothing
272                      , writerVariables        = mempty
273                      , writerTabStop          = 4
274                      , writerTableOfContents  = False
275                      , writerIncremental      = False
276                      , writerHTMLMathMethod   = PlainMath
277                      , writerNumberSections   = False
278                      , writerNumberOffset     = [0,0,0,0,0,0]
279                      , writerSectionDivs      = False
280                      , writerExtensions       = emptyExtensions
281                      , writerReferenceLinks   = False
282                      , writerDpi              = 96
283                      , writerWrapText         = WrapAuto
284                      , writerColumns          = 72
285                      , writerEmailObfuscation = NoObfuscation
286                      , writerIdentifierPrefix = ""
287                      , writerCiteMethod       = Citeproc
288                      , writerHtmlQTags        = False
289                      , writerSlideLevel       = Nothing
290                      , writerTopLevelDivision = TopLevelDefault
291                      , writerListings         = False
292                      , writerHighlightStyle   = Just pygments
293                      , writerSetextHeaders    = False
294                      , writerEpubSubdirectory = "EPUB"
295                      , writerEpubMetadata     = Nothing
296                      , writerEpubFonts        = []
297                      , writerEpubChapterLevel = 1
298                      , writerTOCDepth         = 3
299                      , writerReferenceDoc     = Nothing
300                      , writerReferenceLocation = EndOfDocument
301                      , writerSyntaxMap        = defaultSyntaxMap
302                      , writerPreferAscii      = False
303                      }
304
305instance HasSyntaxExtensions WriterOptions where
306  getExtensions opts = writerExtensions opts
307
308-- | Returns True if the given extension is enabled.
309isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool
310isEnabled ext opts = ext `extensionEnabled` getExtensions opts
311
312defaultMathJaxURL :: Text
313defaultMathJaxURL = "https://cdn.jsdelivr.net/npm/mathjax@3/es5/tex-chtml-full.js"
314
315defaultKaTeXURL :: Text
316defaultKaTeXURL = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.11.1/"
317
318-- Update documentation in doc/filters.md if this is changed.
319$(deriveJSON defaultOptions ''ReaderOptions)
320
321$(deriveJSON defaultOptions{
322   constructorTagModifier = map toLower,
323   sumEncoding = TaggedObject{
324                    tagFieldName = "method",
325                    contentsFieldName = "url" }
326                           } ''HTMLMathMethod)
327
328$(deriveJSON defaultOptions{ constructorTagModifier =
329                               camelCaseStrToHyphenated
330                           } ''CiteMethod)
331
332$(deriveJSON defaultOptions{ constructorTagModifier =
333                            \case
334                                    "NoObfuscation"         -> "none"
335                                    "ReferenceObfuscation"  -> "references"
336                                    "JavascriptObfuscation" -> "javascript"
337                                    _                       -> "none"
338                           } ''ObfuscationMethod)
339
340$(deriveJSON defaultOptions ''HTMLSlideVariant)
341
342-- Update documentation in doc/filters.md if this is changed.
343$(deriveJSON defaultOptions{ constructorTagModifier =
344                               camelCaseStrToHyphenated
345                           } ''TrackChanges)
346
347$(deriveJSON defaultOptions{ constructorTagModifier =
348                               camelCaseStrToHyphenated
349                           } ''WrapOption)
350
351$(deriveJSON defaultOptions{ constructorTagModifier =
352                               camelCaseStrToHyphenated . drop 8
353                           } ''TopLevelDivision)
354
355$(deriveJSON defaultOptions{ constructorTagModifier =
356                               camelCaseStrToHyphenated
357                           } ''ReferenceLocation)
358