aboutsummaryrefslogtreecommitdiff
path: root/test/Haddock
diff options
context:
space:
mode:
authorKazu Yamamoto <kazu@iij.ad.jp>2013-02-01 11:59:24 +0900
committerKazu Yamamoto <kazu@iij.ad.jp>2013-02-01 11:59:24 +0900
commit8d4c94ca5a969a5ebbb791939fb0195dc672429e (patch)
tree560a944a7105cd715f9acba46790bd7e1a77f82f /test/Haddock
parent266a20afd2d27f28bbb62839ebc3f70bd83bfcce (diff)
parent3d25ea2929a9a9bd0768339b8ac5fd1b7c4670ad (diff)
Merge branch 'ghc-7.6' into ghc-7.6-merge-2
Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail.
Diffstat (limited to 'test/Haddock')
-rw-r--r--test/Haddock/ParseSpec.hs81
1 files changed, 81 insertions, 0 deletions
diff --git a/test/Haddock/ParseSpec.hs b/test/Haddock/ParseSpec.hs
new file mode 100644
index 00000000..d692cb0c
--- /dev/null
+++ b/test/Haddock/ParseSpec.hs
@@ -0,0 +1,81 @@
+{-# LANGUAGE OverloadedStrings, StandaloneDeriving, FlexibleInstances, UndecidableInstances, IncoherentInstances #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+module Haddock.ParseSpec (main, spec) where
+
+import Test.Hspec
+import RdrName (RdrName)
+import DynFlags (DynFlags, defaultDynFlags)
+import Haddock.Lex (tokenise)
+import qualified Haddock.Parse as Parse
+import Haddock.Types
+import Outputable (Outputable, showSDoc, ppr)
+import Data.Monoid
+import Data.String
+
+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)
+
+instance IsString (Doc RdrName) where
+ fromString = DocString
+
+parseParas :: String -> Maybe (Doc RdrName)
+parseParas s = Parse.parseParas $ tokenise dynFlags s (0,0)
+
+main :: IO ()
+main = hspec spec
+
+spec :: Spec
+spec = do
+ describe "parseParas" $ do
+ it "parses a paragraph" $ do
+ parseParas "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
+ parseParas "foobar\n\n>>> fib 10\n55" `shouldBe`
+ Just (DocParagraph "foobar\n" <> DocExamples [Example "fib 10" ["55"]])
+
+ -- parse error
+ parseParas "foobar\n>>> fib 10\n55" `shouldBe` Nothing
+
+ it "parses a result line that only contains <BLANKLINE> as an emptly line" $ do
+ parseParas ">>> 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
+ parseParas "foobar\n\n> some code" `shouldBe`
+ Just (DocParagraph "foobar\n" <> DocCodeBlock " some code\n")
+
+ -- parse error
+ parseParas "foobar\n> some code" `shouldBe` Nothing
+
+
+ context "when parsing a URL" $ do
+ it "parses a URL" $ do
+ parseParas "<http://example.com/>" `shouldBe`
+ Just (DocParagraph $ hyperlink "http://example.com/" Nothing <> "\n")
+
+ it "accepts an optional label" $ do
+ parseParas "<http://example.com/ some link>" `shouldBe`
+ Just (DocParagraph $ hyperlink "http://example.com/" (Just "some link") <> "\n")
+
+ context "when parsing properties" $ do
+ it "can parse a single property" $ do
+ parseParas "prop> 23 == 23" `shouldBe` Just (DocProperty "23 == 23")
+
+ it "can parse multiple subsequent properties" $ do
+ parseParas $ 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