diff options
Diffstat (limited to 'src/Text/Pandoc/Options.hs')
-rw-r--r-- | src/Text/Pandoc/Options.hs | 24 |
1 files changed, 13 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index a97c4179d..158303acd 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-} {- Copyright (C) 2012-2015 John MacFarlane <jgm@berkeley.edu> @@ -47,7 +47,6 @@ module Text.Pandoc.Options ( Extension(..) , def , isEnabled ) where -import Prelude import Data.Set (Set) import qualified Data.Set as Set import Data.Default @@ -55,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 = @@ -106,6 +106,7 @@ data Extension = | Ext_ignore_line_breaks -- ^ Newlines in paragraphs are ignored | Ext_literate_haskell -- ^ Enable literate Haskell conventions | Ext_abbreviations -- ^ PHP markdown extra abbreviation definitions + | Ext_emoji -- ^ Support emoji like :smile: | Ext_auto_identifiers -- ^ Automatic identifiers for headers | Ext_ascii_identifiers -- ^ ascii-only identifiers for headers | Ext_header_attributes -- ^ Explicit header attributes {#id .class k=v} @@ -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 @@ -204,6 +205,7 @@ githubMarkdownExtensions = Set.fromList , Ext_intraword_underscores , Ext_strikeout , Ext_hard_line_breaks + , Ext_emoji , Ext_lists_without_preceding_blankline , Ext_shortcut_reference_links ] @@ -257,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{ @@ -279,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 @@ -289,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 @@ -309,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 @@ -362,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 |