module Lentil.Parse.IssueSpec where import Test.Hspec import Text.Parsec ( runParser ) import Text.Parsec.Char import Text.Parsec.Combinator import Control.Applicative import Lentil.Types import Lentil.Parse.Issue -- Parsing tests -- simple parser (choosable if we are at begin of line or else) sp :: ParIssue a -> String -> Maybe a sp p cs = either (const Nothing) Just (runParser p (ParState fp) fp cs) where fp = "" main :: IO () main = hspec spec spec :: Spec spec = do describe "ciString" $ do it "parses a case insensitive string" $ sp (ciString "tEst") "Test" `shouldBe` Just "Test" describe "eoft" $ do it "parses a textfile end of file" $ sp (string "test" <* eoft) "test\n" `shouldBe` Just "test" it "or an eof without '\\n'" $ sp (string "test" <* eoft) "test" `shouldBe` Just "test" describe "blankline" $ do it "parses an empty line" $ sp blankline "\n\nlol" `shouldBe` Just () it "deals with eof blanklines too" $ sp blankline "\n" `shouldBe` Just () describe "htmlify" $ do it "removes unneeded whitespace" $ htmlify "one two " `shouldBe` "one two" it "removes newlines too" $ htmlify "one two\nthree " `shouldBe` "one two three" describe "tag" $ do it "parses a tag" $ fmap tagString (sp tag "[test-tag]") `shouldBe` Just "test-tag" it "should not allow whitespace inside a tag" $ fmap tagString (sp tag "[broken tag]") `shouldBe` Nothing describe "incipit" $ do it "parses the initial section of an issue, returns nothing" $ do sp incipit "\nTODO: " `shouldBe` Just () sp incipit "\nFIXME: " `shouldBe` Just () sp incipit "\nXXX: " `shouldBe` Just () it "doesn't work without previous newline" $ sp incipit "\nTODO:some" `shouldBe` Nothing it "doesn't work if you don't add a space after :" $ sp incipit "\nTODO:some" `shouldBe` Nothing it "does allow you to omit the :" $ sp incipit "\nxxx some" `shouldBe` Just () it "is case unsensitive in flag-word" $ sp incipit "\ntOdO some" `shouldBe` Just () it "allows whitespace before the todo" $ sp incipit "\n fixme some" `shouldBe` Just () it "doesn't allow anything else before flag-words" $ sp incipit "\nso fixme someday" `shouldBe` Nothing it "fails if we are not at the beginning of line" $ sp incipit "\nso fixme someday" `shouldBe` Nothing describe "tags" $ do it "parses a series of tags, sep by whitespace" $ sp tags " [tag] [field:test] [tog]" `shouldBe` Just [Tag "tag", Tag "field:test", Tag "tog"] it "allows ending whitespace" $ sp tags " [tag] [field:test] [tog] " `shouldBe` Just [Tag "tag", Tag "field:test", Tag "tog"] describe "freeText" $ do it "parses a free form text" $ sp freeText "this is it\n\n" `shouldBe` Just "this is it" it "can be ended by tags/fields" $ sp freeText "this is it [field:val]" `shouldBe` Just "this is it" it "trims extra whitespace" $ sp freeText "this is it [bug]" `shouldBe` Just "this is it" it "cannot be ended by new issue on same line" $ sp freeText "this is it TODO: desc\n" `shouldBe` Just "this is it TODO: desc" it "cannot be ended by new issue on new-but-not-beginning-of-line" $ sp freeText "this is it \nn TODO: desc\n" `shouldBe` Just "this is it n TODO: desc" it "can be ended by blank line" $ sp freeText "this is it\n\n TODO: desc" `shouldBe` Just "this is it" it "can be ended by incomplete blank line (eof)" $ sp freeText "this is it\n" `shouldBe` Just "this is it" describe "issue" $ do it "parses an issue" $ sp issue "\n fixMe this is it [t] [f:w]" `shouldBe` (Just $ Issue "" 2 "this is it" [Tag "t", Tag "f:w"]) it "fails if were are not at beginning of a line" $ sp issue "fixMe this is it [t] [f:w]" `shouldBe` Nothing it "parses tagless/fieldless issues too" $ sp issue "\nTODO: this is it\n" `shouldBe` (Just $ Issue "" 2 "this is it" []) it "doesn't display the eventual \n at eof" $ sp issue "\nTOdO: this is it\n" `shouldBe` (Just $ Issue "" 2 "this is it" []) it "doesn't accept a lone (naked) todo" $ sp issue "\ntodo\n" `shouldBe` Nothing describe "issues" $ do it "parses multiple issues" $ sp issues "\nTODO: this is it [f:w]\n TODO: hey [t]" `shouldBe` Just [Issue "" 1 "this is it" [Tag "f:w"], Issue "" 2 "hey" [Tag "t"]] it "don't parse multiple issues if on the same line" $ sp issues "\nTODO: this is it [f:w] TODO: hey [t]" `shouldBe` Just [Issue "" 1 "this is it" [Tag "f:w"]] describe "issueFinder" $ do it "reads a file (code or txt) for issues" $ let fp = "test/test-files/lang-comm/test.txt" in issueFinder [fp] >>= \i -> i `shouldBe` [Issue fp 1 "palla" [], Issue fp 3 "beta" [], Issue fp 4 "gamma" [], Issue fp 6 "qqq" [Tag "bug"]]