aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2013-03-30 09:16:10 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2013-03-30 09:16:10 -0700
commit5aec167e71b3da98a0f209e3c75af019682ad354 (patch)
tree9b40e96cb359b1f223880cb650e83edb4d506c60
parent7cb8b60910ede36bba3598f85a06ddde6fc545d0 (diff)
parent86636677881ab7eace0fd9b2993cfdb01adb7b18 (diff)
downloadpandoc-5aec167e71b3da98a0f209e3c75af019682ad354.tar.gz
Merge pull request #808 from davidlazar/master
Improvements to Haddock reader
-rw-r--r--src/Text/Pandoc/Readers/Haddock.hs6
-rw-r--r--src/Text/Pandoc/Readers/Haddock/Lex.x8
-rw-r--r--src/Text/Pandoc/Readers/Haddock/Parse.y14
3 files changed, 16 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs
index 49154b0ca..081ec7b5e 100644
--- a/src/Text/Pandoc/Readers/Haddock.hs
+++ b/src/Text/Pandoc/Readers/Haddock.hs
@@ -24,8 +24,10 @@ readHaddock :: ReaderOptions -- ^ Reader options
readHaddock _ s = Pandoc (Meta [] [] []) blocks
where
blocks = case parseParas (tokenise s (0,0)) of
- Nothing -> []
- Just x -> mergeLists (toList x)
+ Left [] -> error "parse failure"
+ Left (tok:_) -> error $ "parse failure " ++ pos (tokenPos tok)
+ where pos (l, c) = "(line " ++ show l ++ ", column " ++ show c ++ ")"
+ Right x -> mergeLists (toList x)
-- similar to 'docAppend' in Haddock.Doc
mergeLists :: [Block] -> [Block]
diff --git a/src/Text/Pandoc/Readers/Haddock/Lex.x b/src/Text/Pandoc/Readers/Haddock/Lex.x
index 902ac84c0..a84204e83 100644
--- a/src/Text/Pandoc/Readers/Haddock/Lex.x
+++ b/src/Text/Pandoc/Readers/Haddock/Lex.x
@@ -19,7 +19,8 @@
module Text.Pandoc.Readers.Haddock.Lex (
Token(..),
LToken,
- tokenise
+ tokenise,
+ tokenPos
) where
import Data.Char
@@ -54,14 +55,15 @@ $ident = [$alphanum \'\_\.\!\#\$\%\&\*\+\/\<\=\>\?\@\\\\\^\|\-\~\:]
<line> {
$ws* \> { begin birdtrack }
$ws* \>\>\> { strtoken TokExamplePrompt `andBegin` exampleexpr }
- $ws* \n { token TokPara `andBegin` para }
- -- Here, we really want to be able to say
+ $ws* \n { token TokPara `andBegin` para }
+ -- ^ Here, we really want to be able to say
-- $ws* (\n | <eof>) { token TokPara `andBegin` para}
-- because otherwise a trailing line of whitespace will result in
-- a spurious TokString at the end of a docstring. We don't have <eof>,
-- though (NOW I realise what it was for :-). To get around this, we always
-- append \n to the end of a docstring.
+
() { begin string }
}
diff --git a/src/Text/Pandoc/Readers/Haddock/Parse.y b/src/Text/Pandoc/Readers/Haddock/Parse.y
index 26d7c287d..e34f9d95e 100644
--- a/src/Text/Pandoc/Readers/Haddock/Parse.y
+++ b/src/Text/Pandoc/Readers/Haddock/Parse.y
@@ -46,7 +46,7 @@ import Data.Sequence (viewr, ViewR(..))
PARA { (TokPara,_) }
STRING { (TokString $$,_) }
-%monad { Maybe }
+%monad { Either [LToken] }
%name parseParas doc
%name parseString seq
@@ -76,7 +76,7 @@ defpara :: { (Inlines, [Blocks]) }
para :: { Blocks }
: seq { para' $1 }
- | codepara { codeBlock $1 }
+ | codepara { codeBlockWith ([], ["haskell"], []) $1 }
| property { $1 }
| examples { $1 }
@@ -118,16 +118,16 @@ elem1 :: { Inlines }
| URL { makeHyperlink $1 }
| PIC { image $1 $1 mempty }
| ANAME { mempty } -- TODO
- | IDENT { code $1 }
- | DQUO strings DQUO { code $2 }
+ | IDENT { codeWith ([], ["haskell"], []) $1 }
+ | DQUO strings DQUO { codeWith ([], ["haskell"], []) $2 }
strings :: { String }
: STRING { $1 }
| STRING strings { $1 ++ $2 }
{
-happyError :: [LToken] -> Maybe a
-happyError toks = Nothing
+happyError :: [LToken] -> Either [LToken] a
+happyError toks = Left toks
para' :: Inlines -> Blocks
para' (Many ils) =
@@ -162,7 +162,7 @@ makeProperty s = case strip s of
-- | Create an 'Example', stripping superfluous characters as appropriate
makeExample :: String -> String -> [String] -> Blocks
makeExample prompt expression result =
- para $ codeWith ([], ["expr"], []) (strip expression ++ "\n")
+ para $ codeWith ([], ["haskell", "expr"], []) (strip expression ++ "\n")
<> codeWith ([], ["result"], []) (unlines result')
where
-- 1. drop trailing whitespace from the prompt, remember the prefix