Derive Generic instances for types in Text.Pandoc.Options.
This commit is contained in:
parent
420c86b69a
commit
8f5ff7075c
1 changed files with 11 additions and 10 deletions
|
@ -1,4 +1,4 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
{-
|
||||
Copyright (C) 2012-2015 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -54,6 +54,7 @@ import Text.Pandoc.Highlighting (Style, pygments)
|
|||
import Text.Pandoc.MediaBag (MediaBag)
|
||||
import Data.Data (Data)
|
||||
import Data.Typeable (Typeable)
|
||||
import GHC.Generics (Generic)
|
||||
|
||||
-- | Individually selectable syntax extensions.
|
||||
data Extension =
|
||||
|
@ -114,7 +115,7 @@ data Extension =
|
|||
| Ext_line_blocks -- ^ RST style line blocks
|
||||
| Ext_epub_html_exts -- ^ Recognise the EPUB extended version of HTML
|
||||
| Ext_shortcut_reference_links -- ^ Shortcut reference links
|
||||
deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable)
|
||||
deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable, Generic)
|
||||
|
||||
pandocExtensions :: Set Extension
|
||||
pandocExtensions = Set.fromList
|
||||
|
@ -258,7 +259,7 @@ data ReaderOptions = ReaderOptions{
|
|||
, readerDefaultImageExtension :: String -- ^ Default extension for images
|
||||
, readerTrace :: Bool -- ^ Print debugging info
|
||||
, readerTrackChanges :: TrackChanges
|
||||
} deriving (Show, Read, Data, Typeable)
|
||||
} deriving (Show, Read, Data, Typeable, Generic)
|
||||
|
||||
instance Default ReaderOptions
|
||||
where def = ReaderOptions{
|
||||
|
@ -280,7 +281,7 @@ instance Default ReaderOptions
|
|||
-- Writer options
|
||||
--
|
||||
|
||||
data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable)
|
||||
data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Generic)
|
||||
|
||||
data HTMLMathMethod = PlainMath
|
||||
| LaTeXMathML (Maybe String) -- url of LaTeXMathML.js
|
||||
|
@ -290,18 +291,18 @@ data HTMLMathMethod = PlainMath
|
|||
| MathML (Maybe String) -- url of MathMLinHTML.js
|
||||
| MathJax String -- url of MathJax.js
|
||||
| KaTeX String String -- url of stylesheet and katex.js
|
||||
deriving (Show, Read, Eq, Data, Typeable)
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
data CiteMethod = Citeproc -- use citeproc to render them
|
||||
| Natbib -- output natbib cite commands
|
||||
| Biblatex -- output biblatex cite commands
|
||||
deriving (Show, Read, Eq, Data, Typeable)
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
-- | Methods for obfuscating email addresses in HTML.
|
||||
data ObfuscationMethod = NoObfuscation
|
||||
| ReferenceObfuscation
|
||||
| JavascriptObfuscation
|
||||
deriving (Show, Read, Eq, Data, Typeable)
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
-- | Varieties of HTML slide shows.
|
||||
data HTMLSlideVariant = S5Slides
|
||||
|
@ -310,13 +311,13 @@ data HTMLSlideVariant = S5Slides
|
|||
| DZSlides
|
||||
| RevealJsSlides
|
||||
| NoSlides
|
||||
deriving (Show, Read, Eq, Data, Typeable)
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
-- | Options for accepting or rejecting MS Word track-changes.
|
||||
data TrackChanges = AcceptChanges
|
||||
| RejectChanges
|
||||
| AllChanges
|
||||
deriving (Show, Read, Eq, Data, Typeable)
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
-- | Options for writers
|
||||
data WriterOptions = WriterOptions
|
||||
|
@ -363,7 +364,7 @@ data WriterOptions = WriterOptions
|
|||
, writerMediaBag :: MediaBag -- ^ Media collected by docx or epub reader
|
||||
, writerVerbose :: Bool -- ^ Verbose debugging output
|
||||
, writerLaTeXArgs :: [String] -- ^ Flags to pass to latex-engine
|
||||
} deriving (Show, Data, Typeable)
|
||||
} deriving (Show, Data, Typeable, Generic)
|
||||
|
||||
instance Default WriterOptions where
|
||||
def = WriterOptions { writerStandalone = False
|
||||
|
|
Loading…
Add table
Reference in a new issue