aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorMateusz Kowalczyk <fuuzetsu@fuuzetsu.co.uk>2013-09-08 01:28:57 +0100
committerAustin Seipp <austin@well-typed.com>2014-01-12 14:48:36 -0600
commita03c93524ba2ca4143c10770a2fa0dd134b57a83 (patch)
tree4ad5195b56ffcb92d9897b036e4c629fc7732fd3
parent2aec8fdde55579b62f480c6b2a567bd5392fdff2 (diff)
Allow for nesting of paragraphs under lists.
The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs
-rw-r--r--html-test/ref/Bold.html6
-rw-r--r--html-test/ref/DeprecatedReExport.html3
-rw-r--r--html-test/ref/Nesting.html288
-rw-r--r--html-test/ref/PruneWithWarning.html3
-rw-r--r--html-test/ref/Test.html18
-rw-r--r--html-test/src/Nesting.hs115
-rw-r--r--src/Haddock/Doc.hs2
-rw-r--r--src/Haddock/Parser.hs110
-rw-r--r--src/Haddock/Types.hs2
-rw-r--r--test/Haddock/ParserSpec.hs155
10 files changed, 613 insertions, 89 deletions
diff --git a/html-test/ref/Bold.html b/html-test/ref/Bold.html
index 4d5f559a..f6bdbd5e 100644
--- a/html-test/ref/Bold.html
+++ b/html-test/ref/Bold.html
@@ -68,8 +68,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_Bold.html");};
><li
><strong
>Bold</strong
- > in a list
-</li
+ > in a list</li
></ul
><dl
><dt
@@ -77,8 +76,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_Bold.html");};
>bold in a definition</strong
></dt
><dd
- >list
-</dd
+ >list</dd
></dl
><pre
> bold <strong
diff --git a/html-test/ref/DeprecatedReExport.html b/html-test/ref/DeprecatedReExport.html
index 99b797d0..bf35ab64 100644
--- a/html-test/ref/DeprecatedReExport.html
+++ b/html-test/ref/DeprecatedReExport.html
@@ -63,8 +63,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedReExport.htm
>What is tested here:</p
><ul
><li
- >Deprecation messages are shown for re-exported items.
-</li
+ >Deprecation messages are shown for re-exported items.</li
></ul
></div
></div
diff --git a/html-test/ref/Nesting.html b/html-test/ref/Nesting.html
new file mode 100644
index 00000000..0d692791
--- /dev/null
+++ b/html-test/ref/Nesting.html
@@ -0,0 +1,288 @@
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+<html xmlns="http://www.w3.org/1999/xhtml"
+><head
+ ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"
+ /><title
+ >Nesting</title
+ ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean"
+ /><script src="haddock-util.js" type="text/javascript"
+ ></script
+ ><script type="text/javascript"
+ >//<![CDATA[
+window.onload = function () {pageLoad();setSynopsis("mini_Nesting.html");};
+//]]>
+</script
+ ></head
+ ><body
+ ><div id="package-header"
+ ><ul class="links" id="page-menu"
+ ><li
+ ><a href=""
+ >Contents</a
+ ></li
+ ><li
+ ><a href=""
+ >Index</a
+ ></li
+ ></ul
+ ><p class="caption empty"
+ >&nbsp;</p
+ ></div
+ ><div id="content"
+ ><div id="module-header"
+ ><table class="info"
+ ><tr
+ ><th
+ >Safe Haskell</th
+ ><td
+ >Safe-Inferred</td
+ ></tr
+ ></table
+ ><p class="caption"
+ >Nesting</p
+ ></div
+ ><div id="synopsis"
+ ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')"
+ >Synopsis</p
+ ><ul id="section.syn" class="hide" onclick="toggleSection('syn')"
+ ><li class="src short"
+ ><a href=""
+ >d</a
+ > :: t</li
+ ><li class="src short"
+ ><a href=""
+ >e</a
+ > :: t</li
+ ><li class="src short"
+ ><a href=""
+ >f</a
+ > :: t</li
+ ><li class="src short"
+ ><a href=""
+ >g</a
+ > :: t</li
+ ><li class="src short"
+ ><a href=""
+ >h</a
+ > :: t</li
+ ><li class="src short"
+ ><a href=""
+ >i</a
+ > :: t</li
+ ><li class="src short"
+ ><a href=""
+ >j</a
+ > :: t</li
+ ></ul
+ ></div
+ ><div id="interface"
+ ><h1
+ >Documentation</h1
+ ><div class="top"
+ ><p class="src"
+ ><a name="v:d" class="def"
+ >d</a
+ > :: t</p
+ ><div class="doc"
+ ><ul
+ ><li
+ >We can<ul
+ ><li
+ >easily go back<ol
+ ><li
+ >some indentation</li
+ ></ol
+ ></li
+ ><li
+ >levels</li
+ ></ul
+ ></li
+ ></ul
+ ><ol
+ ><li
+ ><pre
+ >back at the top</pre
+ ></li
+ ></ol
+ ></div
+ ></div
+ ><div class="top"
+ ><p class="src"
+ ><a name="v:e" class="def"
+ >e</a
+ > :: t</p
+ ><div class="doc"
+ ><ul
+ ><li
+ >Beginning of list<ul
+ ><li
+ >second list</li
+ ></ul
+ ></li
+ ><li
+ >Some indented list but
+the presence of this text pushes it out of nesting back to the top.</li
+ ></ul
+ ></div
+ ></div
+ ><div class="top"
+ ><p class="src"
+ ><a name="v:f" class="def"
+ >f</a
+ > :: t</p
+ ><div class="doc"
+ ><ul
+ ><li
+ >Beginning of list<pre
+ >nested code
+ we preserve the space correctly
+</pre
+ ></li
+ ></ul
+ ></div
+ ></div
+ ><div class="top"
+ ><p class="src"
+ ><a name="v:g" class="def"
+ >g</a
+ > :: t</p
+ ><div class="doc"
+ ><ul
+ ><li
+ >Beginning of list<ul
+ ><li
+ >Nested list</li
+ ></ul
+ ></li
+ ></ul
+ ></div
+ ></div
+ ><div class="top"
+ ><p class="src"
+ ><a name="v:h" class="def"
+ >h</a
+ > :: t</p
+ ><div class="doc"
+ ><ul
+ ><li
+ >Beginning of list<pre
+ > nested
+ bird
+ tracks</pre
+ ></li
+ ></ul
+ ></div
+ ></div
+ ><div class="top"
+ ><p class="src"
+ ><a name="v:i" class="def"
+ >i</a
+ > :: t</p
+ ><div class="doc"
+ ><ul
+ ><li
+ >Beginning of list
+This belongs to the list above!<pre
+ > nested
+ bird
+ tracks</pre
+ ><ul
+ ><li
+ >Next list
+More of the indented list.<ul
+ ><li
+ >Deeper<ul
+ ><li
+ >Deeper<ul
+ ><li
+ >Even deeper!</li
+ ><li
+ >No newline separation even in indented lists.</li
+ ></ul
+ ></li
+ ></ul
+ ></li
+ ></ul
+ ></li
+ ></ul
+ ></li
+ ></ul
+ ></div
+ ></div
+ ><div class="top"
+ ><p class="src"
+ ><a name="v:j" class="def"
+ >j</a
+ > :: t</p
+ ><div class="doc"
+ ><dl
+ ><dt
+ >All this</dt
+ ><dd
+ >Works for
+definition lists too.<pre
+ > nested
+ bird
+ tracks</pre
+ ><ul
+ ><li
+ >Next list
+with more of the indented list content.<p
+ >Even more content on a new line.</p
+ ><ol
+ ><li
+ >Different type of list<ol
+ ><li
+ >Deeper</li
+ ></ol
+ ><pre class="screen"
+ ><code class="prompt"
+ >&gt;&gt;&gt; </code
+ ><strong class="userinput"
+ ><code
+ >Here's an example in a list
+</code
+ ></strong
+ >example result
+</pre
+ ><dl
+ ><dt
+ >b</dt
+ ><dd
+ >Even deeper!</dd
+ ><dt
+ >c</dt
+ ><dd
+ >No newline separation even in indented lists.
+ We can have any paragraph level element that we normally
+ can, like headers<p
+ ><h3
+ >Level 3 header</h3
+ ></p
+ ><p
+ >with some content&#8230;</p
+ ><ul
+ ><li
+ >and even more lists inside</li
+ ></ul
+ ></dd
+ ></dl
+ ></li
+ ></ol
+ ></li
+ ></ul
+ ></dd
+ ></dl
+ ></div
+ ></div
+ ></div
+ ></div
+ ><div id="footer"
+ ><p
+ >Produced by <a href=""
+ >Haddock</a
+ > version 2.14.0</p
+ ></div
+ ></body
+ ></html
+>
diff --git a/html-test/ref/PruneWithWarning.html b/html-test/ref/PruneWithWarning.html
index 837c28b4..4fba05b6 100644
--- a/html-test/ref/PruneWithWarning.html
+++ b/html-test/ref/PruneWithWarning.html
@@ -52,8 +52,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_PruneWithWarning.html"
>If a binding has a deprecation message but no documentation, it is pruned
when <code
>OPTIONS_HADDOCK prune</code
- > is used.
-</li
+ > is used.</li
></ul
></div
></div
diff --git a/html-test/ref/Test.html b/html-test/ref/Test.html
index 2a3ae350..b54b3a05 100644
--- a/html-test/ref/Test.html
+++ b/html-test/ref/Test.html
@@ -1632,31 +1632,25 @@ using double quotes: <a href=""
>.</p
><ul
><li
- >This is a bulleted list
-</li
+ >This is a bulleted list</li
><li
- >This is the next item (different kind of bullet)
-</li
+ >This is the next item (different kind of bullet)</li
></ul
><ol
><li
- >This is an ordered list
-</li
+ >This is an ordered list</li
><li
- >This is the next item (different kind of bullet)
-</li
+ >This is the next item (different kind of bullet)</li
></ol
><dl
><dt
>cat</dt
><dd
- >a small, furry, domesticated mammal
-</dd
+ >a small, furry, domesticated mammal</dd
><dt
>pineapple</dt
><dd
- >a fruit grown in the tropics
-</dd
+ >a fruit grown in the tropics</dd
></dl
><pre
> This is a block of code, which can include other markup: <code
diff --git a/html-test/src/Nesting.hs b/html-test/src/Nesting.hs
new file mode 100644
index 00000000..5ab27ec0
--- /dev/null
+++ b/html-test/src/Nesting.hs
@@ -0,0 +1,115 @@
+module Nesting where
+
+{-|
+* We can
+
+ * easily go back
+
+ 1. some indentation
+
+ * levels
+
+1. @back at the top@
+
+-}
+d :: t
+d = undefined
+
+
+{-|
+* Beginning of list
+
+ * second list
+
+ * Some indented list but
+the presence of this text pushes it out of nesting back to the top.
+-}
+e :: t
+e = undefined
+
+
+{-|
+* Beginning of list
+
+ @
+ nested code
+ we preserve the space correctly
+ @
+-}
+f :: t
+f = undefined
+
+
+{-|
+* Beginning of list
+
+ * Nested list
+-}
+g :: t
+g = undefined
+
+{-|
+* Beginning of list
+
+ > nested
+ > bird
+ > tracks
+-}
+h :: t
+h = undefined
+
+{-|
+* Beginning of list
+This belongs to the list above!
+
+ > nested
+ > bird
+ > tracks
+
+ * Next list
+ More of the indented list.
+
+ * Deeper
+
+ * Deeper
+
+ * Even deeper!
+ * No newline separation even in indented lists.
+-}
+i :: t
+i = undefined
+
+
+
+{-|
+[All this] Works for
+definition lists too.
+
+ > nested
+ > bird
+ > tracks
+
+ * Next list
+ with more of the indented list content.
+
+ Even more content on a new line.
+
+ 1. Different type of list
+
+ (2) Deeper
+
+ >>> Here's an example in a list
+ example result
+
+ [b] Even deeper!
+ [c] No newline separation even in indented lists.
+ We can have any paragraph level element that we normally
+ can, like headers
+
+ === Level 3 header
+ with some content…
+
+ * and even more lists inside
+-}
+j :: t
+j = undefined
diff --git a/src/Haddock/Doc.hs b/src/Haddock/Doc.hs
index 69b2dd6f..55d4e303 100644
--- a/src/Haddock/Doc.hs
+++ b/src/Haddock/Doc.hs
@@ -23,6 +23,8 @@ combineDocumentation (Documentation mDoc mWarning) = Just (fromMaybe mempty mW
docAppend :: Doc id -> Doc id -> Doc id
docAppend (DocDefList ds1) (DocDefList ds2) = DocDefList (ds1++ds2)
docAppend (DocDefList ds1) (DocAppend (DocDefList ds2) d) = DocAppend (DocDefList (ds1++ds2)) d
+docAppend (DocOrderedList ds1) (DocOrderedList ds2) = DocOrderedList (ds1 ++ ds2)
+docAppend (DocUnorderedList ds1) (DocUnorderedList ds2) = DocUnorderedList (ds1 ++ ds2)
docAppend DocEmpty d = d
docAppend d DocEmpty = d
docAppend (DocString s1) (DocString s2) = DocString (s1 ++ s2)
diff --git a/src/Haddock/Parser.hs b/src/Haddock/Parser.hs
index 0d24cf17..b8aa9cb4 100644
--- a/src/Haddock/Parser.hs
+++ b/src/Haddock/Parser.hs
@@ -1,4 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE StandaloneDeriving
+ , FlexibleInstances, UndecidableInstances
+ , IncoherentInstances #-}
-- |
-- Module : Haddock.Parser
-- Copyright : (c) Mateusz Kowalczyk 2013,
@@ -12,6 +15,7 @@
module Haddock.Parser (parseString, parseParas, parseStringMaybe, parseParasMaybe) where
import Prelude hiding (takeWhile)
+import Control.Arrow (first)
import Control.Monad (void, mfilter)
import Control.Applicative
import Data.Attoparsec.ByteString.Char8 hiding (parse, take, endOfLine)
@@ -208,36 +212,93 @@ orderedList d = (paren <|> dot) *> innerList (orderedList d) d
innerList :: Parser [Doc RdrName] -> DynFlags -> Parser [Doc RdrName]
innerList item d = do
c <- takeLine
- (cs, items) <- more
- let contents = (docParagraph . parseString d . unlines) (c : cs)
- return (contents : items)
- where
- more :: Parser ([String], [Doc RdrName])
- more = moreListItems <|> moreContent <|> pure ([], [])
-
- moreListItems :: Parser ([String], [Doc RdrName])
- moreListItems = (,) [] <$> (skipSpace *> item)
-
- moreContent :: Parser ([String], [Doc RdrName])
- moreContent = mapFst . (:) <$> nonEmptyLine <*> more
+ (cs, items) <- more item d
+ let contents = docParagraph . parseString d . dropNLs . unlines $ c : cs
+ return $ case items of
+ Left p -> [contents `joinPara` p]
+ Right i -> contents : i
-- | Parses definition lists.
definitionList :: DynFlags -> Parser [(Doc RdrName, Doc RdrName)]
definitionList d = do
- label <- parseStringBS d <$> ("[" *> takeWhile1 (`notElem` "]\n") <* "]")
+ label <- "[" *> (parseStringBS d <$> takeWhile1 (`notElem` "]\n")) <* "]"
c <- takeLine
- (cs, items) <- more
- let contents = (parseString d . unlines) (c : cs)
- return ((label, contents) : items)
+ (cs, items) <- more (definitionList d) d
+ let contents = parseString d . dropNLs . unlines $ c : cs
+ return $ case items of
+ Left p -> [(label, contents `joinPara` p)]
+ Right i -> (label, contents) : i
+
+-- | If possible, appends two 'Doc's under a 'DocParagraph' rather than
+-- outside of it. This allows to get structures like
+--
+-- @DocParagraph (DocAppend … …)@
+--
+-- rather than
+--
+-- @DocAppend (DocParagraph …) …@
+joinPara :: Doc id -> Doc id -> Doc id
+joinPara (DocParagraph p) c = docParagraph $ docAppend p c
+joinPara d p = docAppend d p
+
+-- | Drops all trailing newlines.
+dropNLs :: String -> String
+dropNLs = reverse . dropWhile (== '\n') . reverse
+
+-- | Main worker for 'innerList' and 'definitionList'.
+-- We need the 'Either' here to be able to tell in the respective functions
+-- whether we're dealing with the next list or a nested paragraph.
+more :: Monoid a => Parser a -> DynFlags
+ -> Parser ([String], Either (Doc RdrName) a)
+more item d = innerParagraphs d <|> moreListItems item
+ <|> moreContent item d <|> pure ([], Right mempty)
+
+-- | Use by 'innerList' and 'definitionList' to parse any nested paragraphs.
+innerParagraphs :: DynFlags
+ -> Parser ([String], Either (Doc RdrName) a)
+innerParagraphs d = (,) [] . Left <$> ("\n" *> indentedParagraphs d)
+
+-- | Attemps to fetch the next list if possibly. Used by 'innerList' and
+-- 'definitionList' to recursivly grab lists that aren't separated by a whole
+-- paragraph.
+moreListItems :: Parser a
+ -> Parser ([String], Either (Doc RdrName) a)
+moreListItems item = (,) [] . Right <$> (skipSpace *> item)
+
+-- | Helper for 'innerList' and 'definitionList' which simply takes
+-- a line of text and attempts to parse more list content with 'more'.
+moreContent :: Monoid a => Parser a -> DynFlags
+ -> Parser ([String], Either (Doc RdrName) a)
+moreContent item d = first . (:) <$> nonEmptyLine <*> more item d
+
+-- | Collects and parses the result of 'dropFrontOfPara'
+indentedParagraphs :: DynFlags -> Parser (Doc RdrName)
+indentedParagraphs d = parseParas d . concat <$> dropFrontOfPara " "
+
+-- | Grab as many fully indented paragraphs as we can.
+dropFrontOfPara :: Parser BS.ByteString -> Parser [String]
+dropFrontOfPara sp = do
+ currentParagraph <- some (sp *> takeNonEmptyLine)
+ followingParagraphs <-
+ skipHorizontalSpace *> nextPar -- we have more paragraphs to take
+ <|> skipHorizontalSpace *> nlList -- end of the ride, remember the newline
+ <|> endOfInput *> return [] -- nothing more to take at all
+ return (currentParagraph ++ followingParagraphs)
where
- more :: Parser ([String], [(Doc RdrName, Doc RdrName)])
- more = moreListItems <|> moreContent <|> pure ([], [])
+ nextPar = (++) <$> nlList <*> dropFrontOfPara sp
+ nlList = "\n" *> return ["\n"]
- moreListItems :: Parser ([String], [(Doc RdrName, Doc RdrName)])
- moreListItems = (,) [] <$> (skipSpace *> definitionList d)
+nonSpace :: BS.ByteString -> Parser BS.ByteString
+nonSpace xs
+ | not $ any (not . isSpace) $ decodeUtf8 xs = fail "empty line"
+ | otherwise = return xs
- moreContent :: Parser ([String], [(Doc RdrName, Doc RdrName)])
- moreContent = mapFst . (:) <$> nonEmptyLine <*> more
+-- | Takes a non-empty, not fully whitespace line.
+--
+-- Doesn't discard the trailing newline.
+takeNonEmptyLine :: Parser String
+takeNonEmptyLine = do
+ (++ "\n") . decodeUtf8 <$> (takeWhile1 (/= '\n') >>= nonSpace) <* "\n"
birdtracks :: Parser (Doc a)
birdtracks = DocCodeBlock . DocString . intercalate "\n" <$> many1 line
@@ -263,7 +324,7 @@ examples = DocExamples <$> (many (skipHorizontalSpace *> "\n") *> go)
moreExamples = (,) [] <$> go
result :: Parser ([String], [Example])
- result = mapFst . (:) <$> nonEmptyLine <*> resultAndMoreExamples
+ result = first . (:) <$> nonEmptyLine <*> resultAndMoreExamples
makeExample :: String -> String -> [String] -> Example
makeExample prefix expression res =
@@ -285,9 +346,6 @@ takeLine = decodeUtf8 <$> takeWhile (/= '\n') <* endOfLine
endOfLine :: Parser ()
endOfLine = void "\n" <|> endOfInput
-mapFst :: (a -> b) -> (a, c) -> (b, c)
-mapFst f (a, b) = (f a, b)
-
-- | Property parser.
--
-- >>> parseOnly property "prop> hello world"
diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs
index f90e5496..0a633ec0 100644
--- a/src/Haddock/Types.hs
+++ b/src/Haddock/Types.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
+{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable, StandaloneDeriving #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-----------------------------------------------------------------------------
-- |
diff --git a/test/Haddock/ParserSpec.hs b/test/Haddock/ParserSpec.hs
index b5a9561f..4679661f 100644
--- a/test/Haddock/ParserSpec.hs
+++ b/test/Haddock/ParserSpec.hs
@@ -392,14 +392,85 @@ spec = before initStaticOpts $ do
, Example "fib 10" ["55"]
]
- it "requires an example to be separated from a previous paragraph by an empty line" $ do
- unlines [
- "foobar"
- , ""
- , ">>> fib 10"
- , "55"
- ] `shouldParseTo` DocParagraph "foobar"
- <> DocExamples [Example "fib 10" ["55"]]
+
+ context "when parsing paragraphs nested in lists" $ do
+ it "can nest the same type of list" $ do
+ "* foo\n\n * bar" `shouldParseTo`
+ DocUnorderedList [ DocParagraph $ "foo"
+ <> DocUnorderedList [DocParagraph "bar"]]
+
+ it "can nest another type of list inside" $ do
+ "* foo\n\n 1. bar" `shouldParseTo`
+ DocUnorderedList [ DocParagraph $ "foo"
+ <> DocOrderedList [DocParagraph "bar"]]
+
+ it "can nest a code block inside" $ do
+ "* foo\n\n @foo bar baz@" `shouldParseTo`
+ DocUnorderedList [ DocParagraph $ "foo"
+ <> DocCodeBlock "foo bar baz"]
+
+ "* foo\n\n @\n foo bar baz\n @" `shouldParseTo`
+ DocUnorderedList [ DocParagraph $ "foo"
+ <> DocCodeBlock "foo bar baz\n"]
+
+ it "can nest more than one level" $ do
+ "* foo\n\n * bar\n\n * baz\n qux" `shouldParseTo`
+ DocUnorderedList [ DocParagraph $ "foo"
+ <> DocUnorderedList [ DocParagraph $ "bar"
+ <> DocUnorderedList [DocParagraph "baz\nqux"]
+ ]
+ ]
+
+ it "won't fail on not fully indented paragraph" $ do
+ "* foo\n\n * bar\n\n * qux\nquux" `shouldParseTo`
+ DocUnorderedList [ DocParagraph $ "foo"
+ <> DocUnorderedList [ DocParagraph "bar" ]
+ , DocParagraph "qux\nquux"]
+
+
+ it "can nest definition lists" $ do
+ "[a] foo\n\n [b] bar\n\n [c] baz\n qux" `shouldParseTo`
+ DocDefList [ ("a", "foo"
+ <> DocDefList [ ("b", "bar"
+ <> DocDefList [("c", "baz\nqux")])
+ ])
+ ]
+
+ it "can come back to top level with a different list" $ do
+ "* foo\n\n * bar\n\n1. baz" `shouldParseTo`
+ DocUnorderedList [ DocParagraph $ "foo"
+ <> DocUnorderedList [ DocParagraph "bar" ]
+ ]
+ <> DocOrderedList [ DocParagraph "baz" ]
+
+ it "definition lists can come back to top level with a different list" $ do
+ "[foo] foov\n\n [bar] barv\n\n1. baz" `shouldParseTo`
+ DocDefList [ ("foo", "foov"
+ <> DocDefList [ ("bar", "barv") ])
+ ]
+ <> DocOrderedList [ DocParagraph "baz" ]
+
+
+ context "when parsing consecutive paragraphs" $ do
+ it "will not capture irrelevant consecutive lists" $ do
+ " * bullet\n\n - different bullet\n\n (1) ordered\n \n "
+ ++ "2. different bullet\n \n [cat] kitten\n \n [pineapple] fruit"
+ `shouldParseTo`
+ DocUnorderedList [ DocParagraph "bullet"
+ , DocParagraph "different bullet"]
+ <> DocOrderedList [ DocParagraph "ordered"
+ , DocParagraph "different bullet"
+ ]
+ <> DocDefList [ ("cat", "kitten")
+ , ("pineapple", "fruit")
+ ]
+
+ context "when parsing an example" $ do
+ it ("requires an example to be separated"
+ ++ " from a previous paragraph by an empty line") $ do
+ "foobar\n\n>>> fib 10\n55" `shouldParseTo`
+ DocParagraph "foobar"
+ <> DocExamples [Example "fib 10" ["55"]]
it "parses bird-tracks inside of paragraphs as plain strings" $ do
let xs = "foo\n>>> bar"
@@ -478,9 +549,9 @@ spec = before initStaticOpts $ do
, " * three"
]
`shouldParseTo` DocUnorderedList [
- DocParagraph "one\n"
- , DocParagraph "two\n"
- , DocParagraph "three\n"
+ DocParagraph "one"
+ , DocParagraph "two"
+ , DocParagraph "three"
]
it "ignores empty lines between list items" $ do
@@ -490,8 +561,8 @@ spec = before initStaticOpts $ do
, "* two"
]
`shouldParseTo` DocUnorderedList [
- DocParagraph "one\n"
- , DocParagraph "two\n"
+ DocParagraph "one"
+ , DocParagraph "two"
]
it "accepts an empty list item" $ do
@@ -505,12 +576,12 @@ spec = before initStaticOpts $ do
, "more two"
]
`shouldParseTo` DocUnorderedList [
- DocParagraph "point one\n more one\n"
- , DocParagraph "point two\nmore two\n"
+ DocParagraph "point one\n more one"
+ , DocParagraph "point two\nmore two"
]
it "accepts markup in list items" $ do
- "* /foo/" `shouldParseTo` DocUnorderedList [DocParagraph (DocEmphasis "foo" <> "\n")]
+ "* /foo/" `shouldParseTo` DocUnorderedList [DocParagraph (DocEmphasis "foo")]
it "requires empty lines between list and other paragraphs" $ do
unlines [
@@ -520,7 +591,7 @@ spec = before initStaticOpts $ do
, ""
, "baz"
]
- `shouldParseTo` DocParagraph "foo" <> DocUnorderedList [DocParagraph "bar\n"] <> DocParagraph "baz"
+ `shouldParseTo` DocParagraph "foo" <> DocUnorderedList [DocParagraph "bar"] <> DocParagraph "baz"
context "when parsing ordered lists" $ do
it "parses a simple list" $ do
@@ -530,9 +601,9 @@ spec = before initStaticOpts $ do
, " 3. three"
]
`shouldParseTo` DocOrderedList [
- DocParagraph "one\n"
- , DocParagraph "two\n"
- , DocParagraph "three\n"
+ DocParagraph "one"
+ , DocParagraph "two"
+ , DocParagraph "three"
]
it "ignores empty lines between list items" $ do
@@ -542,8 +613,8 @@ spec = before initStaticOpts $ do
, "2. two"
]
`shouldParseTo` DocOrderedList [
- DocParagraph "one\n"
- , DocParagraph "two\n"
+ DocParagraph "one"
+ , DocParagraph "two"
]
it "accepts an empty list item" $ do
@@ -557,12 +628,12 @@ spec = before initStaticOpts $ do
, "more two"
]
`shouldParseTo` DocOrderedList [
- DocParagraph "point one\n more one\n"
- , DocParagraph "point two\nmore two\n"
+ DocParagraph "point one\n more one"
+ , DocParagraph "point two\nmore two"
]
it "accepts markup in list items" $ do
- "1. /foo/" `shouldParseTo` DocOrderedList [DocParagraph (DocEmphasis "foo" <> "\n")]
+ "1. /foo/" `shouldParseTo` DocOrderedList [DocParagraph (DocEmphasis "foo")]
it "requires empty lines between list and other paragraphs" $ do
unlines [
@@ -572,7 +643,7 @@ spec = before initStaticOpts $ do
, ""
, "baz"
]
- `shouldParseTo` DocParagraph "foo" <> DocOrderedList [DocParagraph "bar\n"] <> DocParagraph "baz"
+ `shouldParseTo` DocParagraph "foo" <> DocOrderedList [DocParagraph "bar"] <> DocParagraph "baz"
context "when parsing definition lists" $ do
it "parses a simple list" $ do
@@ -582,9 +653,9 @@ spec = before initStaticOpts $ do
, " [baz] three"
]
`shouldParseTo` DocDefList [
- ("foo", "one\n")
- , ("bar", "two\n")
- , ("baz", "three\n")
+ ("foo", "one")
+ , ("bar", "two")
+ , ("baz", "three")
]
it "ignores empty lines between list items" $ do
@@ -594,8 +665,8 @@ spec = before initStaticOpts $ do
, "[bar] two"
]
`shouldParseTo` DocDefList [
- ("foo", "one\n")
- , ("bar", "two\n")
+ ("foo", "one")
+ , ("bar", "two")
]
it "accepts an empty list item" $ do
@@ -609,15 +680,15 @@ spec = before initStaticOpts $ do
, "more two"
]
`shouldParseTo` DocDefList [
- ("foo", "point one\n more one\n")
- , ("bar", "point two\nmore two\n")
+ ("foo", "point one\n more one")
+ , ("bar", "point two\nmore two")
]
it "accepts markup in list items" $ do
- "[foo] /foo/" `shouldParseTo` DocDefList [("foo", DocEmphasis "foo" <> "\n")]
+ "[foo] /foo/" `shouldParseTo` DocDefList [("foo", DocEmphasis "foo")]
it "accepts markup for the label" $ do
- "[/foo/] bar" `shouldParseTo` DocDefList [(DocEmphasis "foo", "bar\n")]
+ "[/foo/] bar" `shouldParseTo` DocDefList [(DocEmphasis "foo", "bar")]
it "requires empty lines between list and other paragraphs" $ do
unlines [
@@ -627,7 +698,7 @@ spec = before initStaticOpts $ do
, ""
, "baz"
]
- `shouldParseTo` DocParagraph "foo" <> DocDefList [("foo", "bar\n")] <> DocParagraph "baz"
+ `shouldParseTo` DocParagraph "foo" <> DocDefList [("foo", "bar")] <> DocParagraph "baz"
context "when parsing consecutive paragraphs" $ do
it "accepts consecutive lists" $ do
@@ -644,14 +715,14 @@ spec = before initStaticOpts $ do
, " "
, " [pineapple] fruit"
] `shouldParseTo` DocUnorderedList [
- DocParagraph "foo\n"
- , DocParagraph "bar\n"
+ DocParagraph "foo"
+ , DocParagraph "bar"
] <> DocOrderedList [
- DocParagraph "ordered foo\n"
- , DocParagraph "ordered bar\n"
+ DocParagraph "ordered foo"
+ , DocParagraph "ordered bar"
] <> DocDefList [
- ("cat", "kitten\n")
- , ("pineapple", "fruit\n")
+ ("cat", "kitten")
+ , ("pineapple", "fruit")
]
context "when parsing function documentation headers" $ do