Skip to content

Commit

Permalink
Provide Data.Default instances for ParserState and WriterOptions.
Browse files Browse the repository at this point in the history
Now you can use def (which is re-exported by Text.Pandoc) instead of
defaultParserState or defaultWriterOptions.  For now, these
are still defined too, so existing code need not change.

Closes #546.
  • Loading branch information
John MacFarlane committed Jul 19, 2012
1 parent 26748da commit 2351f7a
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 3 deletions.
3 changes: 3 additions & 0 deletions pandoc.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -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:
Expand Down Expand Up @@ -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:
Expand Down Expand Up @@ -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:
Expand Down
3 changes: 3 additions & 0 deletions src/Text/Pandoc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,8 @@ module Text.Pandoc
, rtfEmbedImage
, jsonFilter
, ToJsonFilter(..)
-- * From Data.Default
, def
) where

import Text.Pandoc.Definition
Expand Down Expand Up @@ -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
Expand Down
8 changes: 6 additions & 2 deletions src/Text/Pandoc/Parsing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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.)
Expand Down Expand Up @@ -658,6 +659,9 @@ data ParserState = ParserState
}
deriving Show

instance Default ParserState where
def = defaultParserState

defaultParserState :: ParserState
defaultParserState =
ParserState { stateParseRaw = False,
Expand Down Expand Up @@ -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
Expand Down
6 changes: 5 additions & 1 deletion src/Text/Pandoc/Shared.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ module Text.Pandoc.Shared (
readDataFile,
-- * Error handling
err,
warn,
warn
) where

import Text.Pandoc.Definition
Expand All @@ -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)

--
Expand Down Expand Up @@ -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
Expand Down

0 comments on commit 2351f7a

Please sign in to comment.