Haddock reader improvements.

- Correctly handle ghci sessions.
- Fixed spacing issues.
- Simplified code.
This commit is contained in:
John MacFarlane 2013-04-14 21:39:05 -07:00
parent 7d7bc2cb79
commit 5c03275a63
2 changed files with 7 additions and 11 deletions

View file

@ -12,6 +12,7 @@ module Text.Pandoc.Readers.Haddock.Parse (parseString, parseParas) where
import Text.Pandoc.Readers.Haddock.Lex import Text.Pandoc.Readers.Haddock.Lex
import Text.Pandoc.Builder import Text.Pandoc.Builder
import Text.Pandoc.Shared (trim, trimr)
import Data.Generics (everywhere, mkT) import Data.Generics (everywhere, mkT)
import Data.Char (isSpace) import Data.Char (isSpace)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
@ -141,13 +142,12 @@ monospace = everywhere (mkT go)
-- A hyperlink consists of a URL and an optional label. The label is separated -- A hyperlink consists of a URL and an optional label. The label is separated
-- from the url by one or more whitespace characters. -- from the url by one or more whitespace characters.
makeHyperlink :: String -> Inlines makeHyperlink :: String -> Inlines
makeHyperlink input = case break isSpace $ strip input of makeHyperlink input = case break isSpace $ trim input of
(url, "") -> link url url (str url) (url, "") -> link url url (str url)
(url, lb) -> link url url (str label) (url, lb) -> link url url (trimInlines $ text lb)
where label = dropWhile isSpace lb
makeProperty :: String -> Blocks makeProperty :: String -> Blocks
makeProperty s = case strip s of makeProperty s = case trim s of
'p':'r':'o':'p':'>':xs -> 'p':'r':'o':'p':'>':xs ->
codeBlockWith ([], ["property"], []) (dropWhile isSpace xs) codeBlockWith ([], ["property"], []) (dropWhile isSpace xs)
xs -> xs ->
@ -156,12 +156,12 @@ makeProperty s = case strip s of
-- | Create an 'Example', stripping superfluous characters as appropriate -- | Create an 'Example', stripping superfluous characters as appropriate
makeExample :: String -> String -> [String] -> Blocks makeExample :: String -> String -> [String] -> Blocks
makeExample prompt expression result = makeExample prompt expression result =
para $ codeWith ([], ["haskell","expr"], []) (strip expression) para $ codeWith ([], ["haskell","expr"], []) (trim expression)
<> linebreak <> linebreak
<> (mconcat $ intersperse linebreak $ map coder result') <> (mconcat $ intersperse linebreak $ map coder result')
where where
-- 1. drop trailing whitespace from the prompt, remember the prefix -- 1. drop trailing whitespace from the prompt, remember the prefix
(prefix, _) = span isSpace prompt prefix = takeWhile isSpace prompt
-- 2. drop, if possible, the exact same sequence of whitespace -- 2. drop, if possible, the exact same sequence of whitespace
-- characters from each result line -- characters from each result line
@ -175,8 +175,4 @@ makeExample prompt expression result =
substituteBlankLine "<BLANKLINE>" = "" substituteBlankLine "<BLANKLINE>" = ""
substituteBlankLine line = line substituteBlankLine line = line
coder = codeWith ([], ["result"], []) coder = codeWith ([], ["result"], [])
-- | Remove all leading and trailing whitespace
strip :: String -> String
strip = dropWhile isSpace . reverse . dropWhile isSpace . reverse
} }

View file

@ -28,4 +28,4 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
[[Plain [Str "The",Space,Str "description",Space,Str "of",Space,Code ("",[],[]) "bar",Str "."]]])] [[Plain [Str "The",Space,Str "description",Space,Str "of",Space,Code ("",[],[]) "bar",Str "."]]])]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "link:",Space,Link [Str "http://haskell.org"] ("http://haskell.org","http://haskell.org")] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "link:",Space,Link [Str "http://haskell.org"] ("http://haskell.org","http://haskell.org")]
,Para [Link [Str "Haskell"] ("http://haskell.org","http://haskell.org"),Space,Str "is",Space,Str "a",Space,Str "fun",Space,Str "language!"] ,Para [Link [Str "Haskell"] ("http://haskell.org","http://haskell.org"),Space,Str "is",Space,Str "a",Space,Str "fun",Space,Str "language!"]
,Para [Link [Str "Click Here!"] ("http://example.com","http://example.com")]] ,Para [Link [Str "Click",Space,Str "Here!"] ("http://example.com","http://example.com")]]