blob: 4a6c8d909c2f9a1c7fb9ef130e05b4b13a5da8af (
plain) (
blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
|
{-# LANGUAGE StandaloneDeriving, FlexibleInstances, UndecidableInstances, IncoherentInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Main (main, spec) where
import Test.Hspec
import RdrName (RdrName)
import DynFlags (DynFlags, defaultDynFlags)
import Haddock.Lex (tokenise)
import Haddock.Parse (parseParas)
import Haddock.Types
import Outputable
import Data.Monoid
dynFlags :: DynFlags
dynFlags = defaultDynFlags (error "dynFlags for Haddock tests: undefined")
instance Outputable a => Show a where
show = showSDoc dynFlags . ppr
deriving instance Show a => Show (Doc a)
deriving instance Eq a =>Eq (Doc a)
parse :: String -> Maybe (Doc RdrName)
parse s = parseParas $ tokenise dynFlags s (0,0)
main :: IO ()
main = hspec spec
spec :: Spec
spec = do
describe "parseParas" $ do
it "parses a paragraph" $ do
parse "foobar" `shouldBe` (Just . DocParagraph . DocString) "foobar\n"
context "when parsing an example" $ do
it "requires an example to be separated from a previous paragrap by an empty line" $ do
parse "foobar\n\n>>> fib 10\n55" `shouldBe`
(Just $ DocAppend (DocParagraph $ DocString "foobar\n") (DocExamples $ [Example "fib 10" ["55"]]))
-- parse error
parse "foobar\n>>> fib 10\n55" `shouldBe` Nothing
it "parses a result line that only contains <BLANKLINE> as an emptly line" $ do
parse ">>> putFooBar\nfoo\n<BLANKLINE>\nbar" `shouldBe`
(Just $ DocExamples $ [Example "putFooBar" ["foo","","bar"]])
context "when parsing a code block" $ do
it "requires a code blocks to be separated from a previous paragrap by an empty line" $ do
parse "foobar\n\n> some code" `shouldBe`
Just (DocAppend (DocParagraph (DocString "foobar\n")) (DocCodeBlock (DocString " some code\n")))
-- parse error
parse "foobar\n> some code" `shouldBe` Nothing
context "when parsing a URL" $ do
it "parses a URL" $ do
parse "<http://example.com/>" `shouldBe`
(Just . DocParagraph $ hyperlink "http://example.com/" Nothing `mappend` DocString "\n")
it "accepts an optional label" $ do
parse "<http://example.com/ some link>" `shouldBe`
(Just . DocParagraph $ hyperlink "http://example.com/" (Just "some link") `mappend` DocString "\n")
where
hyperlink :: String -> Maybe String -> Doc RdrName
hyperlink url = DocHyperlink . Hyperlink url
|