aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
m---------data/templates14
-rw-r--r--deb/stack.yaml2
-rw-r--r--osx/stack.yaml2
-rw-r--r--src/Text/Pandoc/Options.hs21
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs3
5 files changed, 21 insertions, 21 deletions
diff --git a/data/templates b/data/templates
-Subproject ef963c30605d7f0558b9cfbf7183f0aa4aad688
+Subproject c31874467bb58ac1735dc28af458e7603a16639
diff --git a/deb/stack.yaml b/deb/stack.yaml
index dcc76b61c..b4ee36157 100644
--- a/deb/stack.yaml
+++ b/deb/stack.yaml
@@ -13,5 +13,5 @@ flags:
debug: false
packages:
- '..'
-- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.1/pandoc-citeproc-0.8.1.1.tar.gz'
+- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.3/pandoc-citeproc-0.8.1.3.tar.gz'
resolver: lts-3.13
diff --git a/osx/stack.yaml b/osx/stack.yaml
index ec85fb775..71af73661 100644
--- a/osx/stack.yaml
+++ b/osx/stack.yaml
@@ -16,5 +16,5 @@ ghc-options:
highlighting-kate: '-pgmP cpphs -optP--cpp'
packages:
- '..'
-- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.1/pandoc-citeproc-0.8.1.1.tar.gz'
+- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.3/pandoc-citeproc-0.8.1.3.tar.gz'
resolver: lts-3.13
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index b7d268a65..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>
@@ -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
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index ebe678dc0..7ee87f4af 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -191,8 +191,7 @@ writeOpenDocument opts (Pandoc meta blocks) =
listStyle (n,l) = inTags True "text:list-style"
[("style:name", "L" ++ show n)] (vcat l)
listStyles = map listStyle (stListStyles s)
- automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
- reverse $ styles ++ listStyles
+ automaticStyles = vcat $ reverse $ styles ++ listStyles
context = defField "body" body
$ defField "automatic-styles" (render' automaticStyles)
$ metadata