module Lentil.Parse.SourceSpec where import Test.Hspec import Text.Parsec (runParser) import Text.Parsec.Char import Text.Parsec.Combinator import Control.Applicative import Lentil.Parse.Source -- Parsing tests -- simple parser sp :: ParSource a -> String -> Maybe a sp p cs = either (const Nothing) Just (runParser p () fp cs) where fp = "" main :: IO () main = hspec spec spec :: Spec spec = do describe "manyTill1" $ do it "behaves like manyTill on non-empty string" $ sp (manyTill1 anyChar newline) "foo\n" `shouldBe` sp (manyTill anyChar newline) "foo\n" it "doesn't runtime crash on a empty string (instead returns [])" $ sp (manyTill1 anyChar newline) "" `shouldBe` Just [] describe "lineComment" $ do it "parses a line comment" $ sp (lineComment "//") "// Test\n" `shouldBe` Just " Test\n" it "fails without trailing \\n" $ sp (lineComment "//") "// Test" `shouldBe` Nothing describe "blockComment" $ do it "parses a block comment" $ sp (blockComment ("/*","*/")) "/* Test\n2 */" `shouldBe` Just " Test\n2 " describe "litString" $ do it "parses code string" $ sp (litString '"') "\"palla\"" `shouldBe` Just "palla" it "parses code string with escaped \" inside" $ sp (litString '"') "\"pal\\\"la\"" `shouldBe` Just "pal\"la" it "parses code string with comments symbols inside" $ sp (litString '"') "\"pal#la\"" `shouldBe` Just "pal#la" describe "litChar" $ do it "parses a string literal character inside" $ sp (litChar '\'') "'a'" `shouldBe` Just 'a' it "parses escaped characters too" $ sp (litChar '\'') "'\"'" `shouldBe` Just '\"' let hss = ParSyntax ["--"] [("{-", "-}")] ['"'] ['\''] describe "program" $ do it "parses program instructions till eof" $ sp (program hss) "prova " `shouldBe` Just "prova " it "stops at single-line comment" $ sp (program hss) "prova -- " `shouldBe` Just "prova " it "stops at blockcomment" $ sp (program hss) "prova {- " `shouldBe` Just "prova " it "stops at literal string" $ sp (program hss) "prova \"babby " `shouldBe` Just "prova " it "stops at literal char" $ sp (program hss) "prova ' '" `shouldBe` Just "prova " it "stops at ' which is not a literal char" $ sp (program hss) "prova' " `shouldBe` Just "prova' " let rbs = ParSyntax ["#"] [] ['"', '\''] [] describe "source" $ do it "parses one piece of source (line-comment)" $ sp (source hss) "-- hey\n my " `shouldBe` Just " hey\n" it "parses one piece of source (block-comment)" $ sp (source hss) "{-hey-}\n my " `shouldBe` Just "hey" it "parses one piece of source (string-literal)" $ sp (source hss) "\"hey\"" `shouldBe` Just "" it "parses a string for language with ' and \" available" $ sp (source rbs) "\"he#y\"" `shouldBe` Just "" it "parses one piece of source (char-literal)" $ sp (source hss) "\'h\'" `shouldBe` Just "" it "parses one piece of source (program instructions)" $ sp (source hss) "prime'" `shouldBe` Just "" describe "commentParser" $ do beforeAll (readFile "test/test-files/lang-comm/out.blocks") $ do it "parses a haskell source" (\a -> commentParser "test/test-files/lang-comm/haskell.hs" >>= \s -> s `shouldBe` Just a) it "parses a C source" (\a -> commentParser "test/test-files/lang-comm/clang.c" >>= \s -> s `shouldBe` Just a) it "parses a Pascal source" (\a -> commentParser "test/test-files/lang-comm/pascal.pas" >>= \s -> s `shouldBe` Just a) it "parses a plain text source" (\a -> commentParser "test/test-files/lang-comm/text.txt" >>= \s -> s `shouldBe` Just a) it "parses a javascript source" (\a -> commentParser "test/test-files/lang-comm/javascript.js" >>= \s -> s `shouldBe` Just a) it "parses a python source" (\a -> commentParser "test/test-files/lang-comm/python.py" >>= \s -> s `shouldBe` Just a) it "parses a ruby source" (\a -> commentParser "test/test-files/lang-comm/ruby.rb" >>= \s -> s `shouldBe` Just a)