[commit: haddock] master: Add basic tests related to comment parsing. (f3d1f3c)
git at git.haskell.org
git at git.haskell.org
Wed Jul 8 08:41:21 UTC 2015
Repository : ssh://git@git.haskell.org/haddock
On branch : master
Link : http://git.haskell.org/haddock.git/commitdiff/f3d1f3cbd6e99f5d477a78e05c13b65b9e8b3fae
>---------------------------------------------------------------
commit f3d1f3cbd6e99f5d477a78e05c13b65b9e8b3fae
Author: Łukasz Hanuszczak <lukasz.hanuszczak at gmail.com>
Date: Sun Jun 28 00:49:17 2015 +0200
Add basic tests related to comment parsing.
>---------------------------------------------------------------
f3d1f3cbd6e99f5d477a78e05c13b65b9e8b3fae
.../src/Haddock/Backends/Hyperlinker/Parser.hs | 2 +-
.../Haddock/Backends/Hyperlinker/ParserSpec.hs | 37 +++++++++++++++++++++-
2 files changed, 37 insertions(+), 2 deletions(-)
diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
index bab5ba0..019075a 100644
--- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
@@ -38,7 +38,7 @@ data TokenType
| TkCpp
| TkPragma
| TkUnknown
- deriving (Eq)
+ deriving (Show, Eq)
-- | Turn source code string into a stream of more descriptive tokens.
--
diff --git a/haddock-api/test/Haddock/Backends/Hyperlinker/ParserSpec.hs b/haddock-api/test/Haddock/Backends/Hyperlinker/ParserSpec.hs
index c85fa47..d596422 100644
--- a/haddock-api/test/Haddock/Backends/Hyperlinker/ParserSpec.hs
+++ b/haddock-api/test/Haddock/Backends/Hyperlinker/ParserSpec.hs
@@ -9,9 +9,44 @@ import Haddock.Backends.Hyperlinker.Parser
main :: IO ()
main = hspec spec
+
spec :: Spec
spec = do
describe "parse" parseSpec
+
parseSpec :: Spec
-parseSpec = return ()
+parseSpec = do
+
+ context "when parsing single-line comments" $ do
+
+ it "should ignore content until the end of line" $
+ "-- some very simple comment\nidentifier"
+ `shouldParseTo`
+ [TkComment, TkSpace, TkIdentifier]
+
+ it "should allow endline escaping" $
+ "-- first line\\\nsecond line\\\nand another one"
+ `shouldParseTo`
+ [TkComment]
+
+ context "when parsing multi-line comments" $ do
+
+ it "should support nested comments" $
+ "{- comment {- nested -} still comment -} {- next comment -}"
+ `shouldParseTo`
+ [TkComment, TkSpace, TkComment]
+
+ it "should distinguish compiler pragma" $
+ "{- comment -}{-# LANGUAGE GADTs #-}{- comment -}"
+ `shouldParseTo`
+ [TkComment, TkPragma, TkComment]
+
+ it "should recognize preprocessor directives" $ do
+ "\n#define foo bar" `shouldParseTo` [TkSpace, TkCpp]
+ "x # y" `shouldParseTo`
+ [TkIdentifier, TkSpace, TkCpp, TkSpace,TkIdentifier]
+
+
+shouldParseTo :: String -> [TokenType] -> Expectation
+str `shouldParseTo` tokens = map tkType (parse str) `shouldBe` tokens
More information about the ghc-commits
mailing list