Skip to content
Snippets Groups Projects
Commit 6889ef69 authored by sol's avatar sol
Browse files

Add support for blank lines in the result of examples

Result lines that only contain the string "<BLANKLINE>" are treated as a blank
line.
parent 3a048f0e
No related branches found
No related tags found
5 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!12Drop orphan instance when defined upstream.,!10Haddock interfaces produced from `.hi` files
......@@ -129,14 +129,21 @@ makeExample prompt expression result =
-- whitespace in expressions, so drop them
result'
where
-- drop trailing whitespace from the prompt, remember the prefix
-- 1. drop trailing whitespace from the prompt, remember the prefix
(prefix, _) = span isSpace prompt
-- drop, if possible, the exact same sequence of whitespace characters
-- from each result line
result' = map (tryStripPrefix prefix) result
-- 2. drop, if possible, the exact same sequence of whitespace
-- characters from each result line
--
-- 3. interpret lines that only contain the string "<BLANKLINE>" as an
-- empty line
result' = map (substituteBlankLine . tryStripPrefix prefix) result
where
tryStripPrefix xs ys = fromMaybe ys $ stripPrefix xs ys
substituteBlankLine "<BLANKLINE>" = ""
substituteBlankLine line = line
-- | Remove all leading and trailing whitespace
strip :: String -> String
strip = dropWhile isSpace . reverse . dropWhile isSpace . reverse
......
......@@ -28,6 +28,11 @@ module Examples where
-- >>> isSpace 'a'
-- False
--
-- >>> putStrLn "foo\n\nbar"
-- foo
-- <BLANKLINE>
-- bar
--
fib :: Integer -> Integer
fib 0 = 0
fib 1 = 1
......
......@@ -135,6 +135,18 @@ window.onload = function () {pageLoad();setSynopsis("mini_Examples.html");};
</code
></strong
>False
</pre
><pre class="screen"
><code class="prompt"
>&gt;&gt;&gt; </code
><strong class="userinput"
><code
>putStrLn &quot;foo\n\nbar&quot;
</code
></strong
>foo
bar
</pre
></div
></div
......
......@@ -41,6 +41,12 @@ tests = [
input = "foobar\n> some code"
, result = Nothing -- parse error
}
-- test <BLANKLINE> support
, ParseTest {
input = ">>> putFooBar\nfoo\n<BLANKLINE>\nbar"
, result = Just $ DocExamples $ [Example "putFooBar" ["foo","","bar"]]
}
]
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment