aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc.hs12
-rw-r--r--src/Text/Pandoc/Options.hs30
-rw-r--r--src/Text/Pandoc/Parsing.hs4
3 files changed, 26 insertions, 20 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 193755dff..95fec7360 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -170,16 +170,22 @@ readers = [("native" , \_ -> readNative)
,("json" , \_ -> decodeJSON)
,("markdown" , readMarkdown)
,("markdown+lhs" , \st ->
- readMarkdown st{ stateLiterateHaskell = True})
+ readMarkdown st{ stateOptions =
+ let oldopts = stateOptions st
+ in oldopts{ readerLiterateHaskell = True} })
,("rst" , readRST)
,("rst+lhs" , \st ->
- readRST st{ stateLiterateHaskell = True})
+ readRST st{ stateOptions =
+ let oldopts = stateOptions st
+ in oldopts{ readerLiterateHaskell = True} })
,("docbook" , readDocBook)
,("textile" , readTextile) -- TODO : textile+lhs
,("html" , readHtml)
,("latex" , readLaTeX)
,("latex+lhs" , \st ->
- readLaTeX st{ stateLiterateHaskell = True})
+ readLaTeX st{ stateOptions =
+ let oldopts = stateOptions st
+ in oldopts{ readerLiterateHaskell = True} })
]
data Writer = PureStringWriter (WriterOptions -> Pandoc -> String)
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index bd04a4373..063162718 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -51,24 +51,26 @@ data Extension = Footnotes
deriving (Show, Read, Enum, Eq, Ord, Bounded)
data ReaderOptions = ReaderOptions{
- readerExtensions :: Set Extension -- ^ Syntax extensions
- , readerSmart :: Bool -- ^ Smart punctuation
- , readerStrict :: Bool -- ^ FOR TRANSITION ONLY
- , readerParseRaw :: Bool -- ^ Parse raw HTML, LaTeX
- , readerColumns :: Int -- ^ Number of columns in terminal
- , readerTabStop :: Int -- ^ Tab stop
- , readerOldDashes :: Bool -- ^ Use pandoc <= 1.8.2.1 behavior
+ readerExtensions :: Set Extension -- ^ Syntax extensions
+ , readerSmart :: Bool -- ^ Smart punctuation
+ , readerStrict :: Bool -- ^ FOR TRANSITION ONLY
+ , readerParseRaw :: Bool -- ^ Parse raw HTML, LaTeX
+ , readerColumns :: Int -- ^ Number of columns in terminal
+ , readerTabStop :: Int -- ^ Tab stop
+ , readerOldDashes :: Bool -- ^ Use pandoc <= 1.8.2.1 behavior
-- in parsing dashes; -- is em-dash;
-- - before numerial is en-dash
+ , readerLiterateHaskell :: Bool -- ^ Interpret as literate Haskell
} deriving (Show, Read)
instance Default ReaderOptions
where def = ReaderOptions{
- readerExtensions = Set.fromList [minBound..maxBound]
- , readerSmart = False
- , readerStrict = False
- , readerParseRaw = False
- , readerColumns = 80
- , readerTabStop = 4
- , readerOldDashes = False
+ readerExtensions = Set.fromList [minBound..maxBound]
+ , readerSmart = False
+ , readerStrict = False
+ , readerParseRaw = False
+ , readerColumns = 80
+ , readerTabStop = 4
+ , readerOldDashes = False
+ , readerLiterateHaskell = False
}
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 9c553a9ed..a266c527e 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -395,7 +395,7 @@ failIfStrict = getOption readerStrict >>= guard . not
-- | Fail unless we're in literate haskell mode.
failUnlessLHS :: Parsec [tok] ParserState ()
-failUnlessLHS = getState >>= guard . stateLiterateHaskell
+failUnlessLHS = getOption readerLiterateHaskell >>= guard
-- | Parses backslash, then applies character parser.
escaped :: Parsec [Char] st Char -- ^ Parser for character to escape
@@ -698,7 +698,6 @@ data ParserState = ParserState
stateTitle :: [Inline], -- ^ Title of document
stateAuthors :: [[Inline]], -- ^ Authors of document
stateDate :: [Inline], -- ^ Date of document
- stateLiterateHaskell :: Bool, -- ^ Treat input as literate haskell
stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used
stateIndentedCodeClasses :: [String], -- ^ Classes to use for indented code blocks
stateNextExample :: Int, -- ^ Number of next example
@@ -726,7 +725,6 @@ defaultParserState =
stateTitle = [],
stateAuthors = [],
stateDate = [],
- stateLiterateHaskell = False,
stateHeaderTable = [],
stateIndentedCodeClasses = [],
stateNextExample = 1,