diff options
Diffstat (limited to 'tests')
-rw-r--r-- | tests/unit-tests/Haddock/ParseSpec.hs | 34 |
1 files changed, 18 insertions, 16 deletions
diff --git a/tests/unit-tests/Haddock/ParseSpec.hs b/tests/unit-tests/Haddock/ParseSpec.hs index 0c959982..f7b32fb8 100644 --- a/tests/unit-tests/Haddock/ParseSpec.hs +++ b/tests/unit-tests/Haddock/ParseSpec.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE StandaloneDeriving, FlexibleInstances, UndecidableInstances, IncoherentInstances #-} +{-# LANGUAGE OverloadedStrings, StandaloneDeriving, FlexibleInstances, UndecidableInstances, IncoherentInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Haddock.ParseSpec (main, spec) where @@ -8,8 +8,9 @@ import DynFlags (DynFlags, defaultDynFlags) import Haddock.Lex (tokenise) import Haddock.Parse (parseParas) import Haddock.Types -import Outputable +import Outputable (Outputable, showSDoc, ppr) import Data.Monoid +import Data.String dynFlags :: DynFlags dynFlags = defaultDynFlags (error "dynFlags for Haddock tests: undefined") @@ -20,6 +21,9 @@ instance Outputable a => Show a where deriving instance Show a => Show (Doc a) deriving instance Eq a =>Eq (Doc a) +instance IsString (Doc RdrName) where + fromString = DocString + parse :: String -> Maybe (Doc RdrName) parse s = parseParas $ tokenise dynFlags s (0,0) @@ -29,27 +33,25 @@ main = hspec spec spec :: Spec spec = do describe "parseParas" $ do - it "parses a paragraph" $ do - parse "foobar" `shouldBe` (Just . DocParagraph . DocString) "foobar\n" + parse "foobar" `shouldBe` Just (DocParagraph "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"]])) + Just (DocParagraph "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"]]) + 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"))) + Just (DocParagraph "foobar\n" <> DocCodeBlock " some code\n") -- parse error parse "foobar\n> some code" `shouldBe` Nothing @@ -58,22 +60,22 @@ spec = do 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") + Just (DocParagraph $ hyperlink "http://example.com/" Nothing <> "\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") + Just (DocParagraph $ hyperlink "http://example.com/" (Just "some link") <> "\n") context "when parsing properties" $ do it "can parse a single property" $ do - parse "prop> 23 == 23" `shouldBe` (Just $ DocProperty "23 == 23") + parse "prop> 23 == 23" `shouldBe` Just (DocProperty "23 == 23") it "can parse a multiple subsequent properties" $ do - let input = unlines [ - "prop> 23 == 23" - , "prop> 42 == 42" - ] - parse input `shouldBe` (Just $ DocProperty "23 == 23" `DocAppend` DocProperty "42 == 42") + parse $ unlines [ + "prop> 23 == 23" + , "prop> 42 == 42" + ] + `shouldBe` Just (DocProperty "23 == 23" <> DocProperty "42 == 42") where hyperlink :: String -> Maybe String -> Doc RdrName hyperlink url = DocHyperlink . Hyperlink url |