aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2015-03-19 09:16:54 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2015-03-19 09:16:54 -0700
commit787664d5fc64e934fbd0bda340c0ad31a9704d1b (patch)
treed0162fcb4ea6189880fd96c477cd5be09b9f4935
parent0a82e7e4b1d912108d0dc909d7e4969464b28fd8 (diff)
parente952d6633fbfb6355ad41ae9898d72982892e11a (diff)
downloadpandoc-787664d5fc64e934fbd0bda340c0ad31a9704d1b.tar.gz
Merge pull request #2013 from ShabbyX/master
Derive from Data and Typeable for libpandoc
-rw-r--r--src/Text/Pandoc/MediaBag.hs6
-rw-r--r--src/Text/Pandoc/Options.hs21
2 files changed, 16 insertions, 11 deletions
diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs
index a55d5417e..1246cdc8f 100644
--- a/src/Text/Pandoc/MediaBag.hs
+++ b/src/Text/Pandoc/MediaBag.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable #-}
{-
Copyright (C) 2014 John MacFarlane <jgm@berkeley.edu>
@@ -46,13 +46,15 @@ import Text.Pandoc.MIME (MimeType, getMimeTypeDef)
import qualified Text.Pandoc.UTF8 as UTF8
import Data.Maybe (fromMaybe)
import System.IO (stderr)
+import Data.Data (Data)
+import Data.Typeable (Typeable)
-- | A container for a collection of binary resources, with names and
-- mime types. Note that a 'MediaBag' is a Monoid, so 'mempty'
-- can be used for an empty 'MediaBag', and '<>' can be used to append
-- two 'MediaBag's.
newtype MediaBag = MediaBag (M.Map [String] (MimeType, BL.ByteString))
- deriving (Monoid)
+ deriving (Monoid, Data, Typeable)
instance Show MediaBag where
show bag = "MediaBag " ++ show (mediaDirectory bag)
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index bde7454e2..1776d14e5 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE DeriveDataTypeable #-}
{-
Copyright (C) 2012-2014 John MacFarlane <jgm@berkeley.edu>
@@ -51,6 +52,8 @@ import Data.Default
import Text.Pandoc.Highlighting (Style, pygments)
import Text.Pandoc.MediaBag (MediaBag)
import Data.Monoid
+import Data.Data (Data)
+import Data.Typeable (Typeable)
-- | Individually selectable syntax extensions.
data Extension =
@@ -110,7 +113,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)
+ deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable)
pandocExtensions :: Set Extension
pandocExtensions = Set.fromList
@@ -226,7 +229,7 @@ data ReaderOptions = ReaderOptions{
, readerDefaultImageExtension :: String -- ^ Default extension for images
, readerTrace :: Bool -- ^ Print debugging info
, readerTrackChanges :: TrackChanges
-} deriving (Show, Read)
+} deriving (Show, Read, Data, Typeable)
instance Default ReaderOptions
where def = ReaderOptions{
@@ -248,7 +251,7 @@ instance Default ReaderOptions
-- Writer options
--
-data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read)
+data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable)
data HTMLMathMethod = PlainMath
| LaTeXMathML (Maybe String) -- url of LaTeXMathML.js
@@ -258,18 +261,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)
+ deriving (Show, Read, Eq, Data, Typeable)
data CiteMethod = Citeproc -- use citeproc to render them
| Natbib -- output natbib cite commands
| Biblatex -- output biblatex cite commands
- deriving (Show, Read, Eq)
+ deriving (Show, Read, Eq, Data, Typeable)
-- | Methods for obfuscating email addresses in HTML.
data ObfuscationMethod = NoObfuscation
| ReferenceObfuscation
| JavascriptObfuscation
- deriving (Show, Read, Eq)
+ deriving (Show, Read, Eq, Data, Typeable)
-- | Varieties of HTML slide shows.
data HTMLSlideVariant = S5Slides
@@ -278,13 +281,13 @@ data HTMLSlideVariant = S5Slides
| DZSlides
| RevealJsSlides
| NoSlides
- deriving (Show, Read, Eq)
+ deriving (Show, Read, Eq, Data, Typeable)
-- | Options for accepting or rejecting MS Word track-changes.
data TrackChanges = AcceptChanges
| RejectChanges
| AllChanges
- deriving (Show, Read, Eq)
+ deriving (Show, Read, Eq, Data, Typeable)
-- | Options for writers
data WriterOptions = WriterOptions
@@ -331,7 +334,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
+ } deriving (Show, Data, Typeable)
instance Default WriterOptions where
def = WriterOptions { writerStandalone = False