aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--pandoc.cabal3
-rw-r--r--src/Text/Pandoc.hs3
-rw-r--r--src/Text/Pandoc/Parsing.hs8
-rw-r--r--src/Text/Pandoc/Shared.hs6
4 files changed, 17 insertions, 3 deletions
diff --git a/pandoc.cabal b/pandoc.cabal
index 139e576ec..f1f7c6f4d 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -223,6 +223,7 @@ Library
base64-bytestring >= 0.1 && < 0.2,
zlib >= 0.5 && < 0.6,
highlighting-kate >= 0.5.1 && < 0.6,
+ data-default >= 0.4 && < 0.6,
temporary >= 1.1 && < 1.2
if flag(blaze_html_0_5)
build-depends:
@@ -331,6 +332,7 @@ Executable pandoc
base64-bytestring >= 0.1 && < 0.2,
zlib >= 0.5 && < 0.6,
highlighting-kate >= 0.5.1 && < 0.6,
+ data-default >= 0.4 && < 0.6,
temporary >= 1.1 && < 1.2
if flag(blaze_html_0_5)
build-depends:
@@ -398,6 +400,7 @@ Executable test-pandoc
base64-bytestring >= 0.1 && < 0.2,
zlib >= 0.5 && < 0.6,
highlighting-kate >= 0.5.1 && < 0.6,
+ data-default >= 0.4 && < 0.6,
temporary >= 1.1 && < 1.2
if flag(blaze_html_0_5)
build-depends:
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 432a5c2ba..f3436cc7b 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -114,6 +114,8 @@ module Text.Pandoc
, rtfEmbedImage
, jsonFilter
, ToJsonFilter(..)
+ -- * From Data.Default
+ , def
) where
import Text.Pandoc.Definition
@@ -149,6 +151,7 @@ import Text.Pandoc.Shared
import Data.Version (showVersion)
import Text.JSON.Generic
import Paths_pandoc (version)
+import Data.Default
-- | Version number of pandoc library.
pandocVersion :: String
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index cac2b71ca..70a8586db 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -88,6 +88,7 @@ import Text.Pandoc.Shared
import qualified Data.Map as M
import Text.TeXMath.Macros (applyMacros, Macro, parseMacroDefinitions)
import Text.HTML.TagSoup.Entity ( lookupEntity )
+import Data.Default
-- | Like >>, but returns the operation on the left.
-- (Suggested by Tillmann Rendel on Haskell-cafe list.)
@@ -658,6 +659,9 @@ data ParserState = ParserState
}
deriving Show
+instance Default ParserState where
+ def = defaultParserState
+
defaultParserState :: ParserState
defaultParserState =
ParserState { stateParseRaw = False,
@@ -872,13 +876,13 @@ macro = do
inp <- getInput
case parseMacroDefinitions inp of
([], _) -> pzero
- (ms, rest) -> do def <- count (length inp - length rest) anyChar
+ (ms, rest) -> do def' <- count (length inp - length rest) anyChar
if apply
then do
updateState $ \st ->
st { stateMacros = ms ++ stateMacros st }
return Null
- else return $ RawBlock "latex" def
+ else return $ RawBlock "latex" def'
-- | Apply current macros to string.
applyMacros' :: String -> GenParser Char ParserState String
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index f14a57c1f..6c8904010 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -72,7 +72,7 @@ module Text.Pandoc.Shared (
readDataFile,
-- * Error handling
err,
- warn,
+ warn
) where
import Text.Pandoc.Definition
@@ -94,6 +94,7 @@ import Text.Pandoc.Highlighting (Style, pygments)
import Text.Pandoc.Pretty (charWidth)
import System.Locale (defaultTimeLocale)
import Data.Time
+import Data.Default
import System.IO (stderr)
--
@@ -524,6 +525,9 @@ data WriterOptions = WriterOptions
, writerTeXLigatures :: Bool -- ^ Use tex ligatures quotes, dashes in latex
} deriving Show
+instance Default WriterOptions where
+ def = defaultWriterOptions
+
{-# DEPRECATED writerXeTeX "writerXeTeX no longer does anything" #-}
-- | Default writer options.
defaultWriterOptions :: WriterOptions