module Lentil.Parse.IssueSpec where import Test.Hspec import Text.Parsec ( runParser ) import Text.Parsec.Char import Control.Applicative import Lentil.Types import Lentil.Parse.Issue import Prelude -- 7.8 hack -- Parsing tests -- simple parser (choosable if we are at begin of line or else) sp :: [FlagWord] -> ParIssue a -> String -> Maybe a sp fws p cs = either (const Nothing) Just (runParser p fws fp cs) where fp = "" main :: IO () main = hspec spec spec :: Spec spec = do describe "normaliseFlagword" $ do it "normalises the capitalisation of a flag-word" $ normaliseFlagword "TODO" `shouldBe` "todo" it "normalises capitalisation midword" $ normaliseFlagword "tOdo" `shouldBe` "todo" it "correctly handles empty strings" $ normaliseFlagword "" `shouldBe` "" 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 "\n TODO: " `shouldBe` Just "todo" sp [] incipit "\n FIXME: " `shouldBe` Just "fixme" sp [] incipit "\nXXX: " `shouldBe` Just "xxx" it "parses the initial section of an issue (user-defined flagword)" $ sp ["feature"] incipit "\n Feature: " `shouldBe` Just "feature" it "parses the initial sect. (user-defined, normalising)" $ sp ["feaTure"] incipit "\n Feature: " `shouldBe` Just "feature" it "doesn't work without previous newline" $ sp [] incipit "\nTODO:some" `shouldBe` Nothing it "doesn't work with longer matches (todoodle)" $ sp [] incipit "\nTODOodle:some" `shouldBe` Nothing it "doesn't work if you don't add a space after :" $ do sp [] incipit "\nTODO:some" `shouldBe` Nothing sp [] incipit "\nTODO_some" `shouldBe` Nothing it "does allow you to omit the :" $ sp [] incipit "\nxxx some" `shouldBe` Just "xxx" it "is case unsensitive in flag-word" $ sp [] incipit "\ntOdO some" `shouldBe` Just "todo" it "doesn't allow anything before flag-words" $ sp [] incipit "so fixme someday" `shouldBe` Nothing it "fails if we are not at the beginning of line" $ sp [] incipit "so 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 (Just "this is it") it "can be ended by tags/fields" $ sp [] freeText "this is it [field:val]" `shouldBe` Just (Just "this is it") it "trims extra whitespace" $ sp [] freeText "this is it [bug]" `shouldBe` Just (Just "this is it") it "cannot be ended by new issue on same line" $ sp [] freeText "this is it TODO: desc\n" `shouldBe` Just (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 (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 (Just "this is it") it "can be ended by incomplete blank line (eof)" $ sp [] freeText "this is it\n" `shouldBe` Just (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 (Just "this is it") [Tag "fixme", Tag "t", Tag "f:w"]) it "parses tagless/fieldless issues too" $ sp [] issue "\nTODO: this is it\n" `shouldBe` (Just $ Issue "" 2 (Just "this is it") []) it "parses an issue not ended by \\n" $ sp [] issue "\ntodo block1 " `shouldBe` (Just $ Issue "" 2 (Just "block1") []) it "doesn't display the eventual \\n at eof" $ sp [] issue "\nTOdO: this is it\n" `shouldBe` (Just $ Issue "" 2 (Just "this is it") []) it "does accept a lone (naked) todo" $ sp [] issue "\ntodo\n" `shouldBe` (Just $ Issue "" 2 Nothing []) it "issues declared with fixme get a free [fixme] tag" $ sp [] issue "\nfixme blah\n" `shouldBe` (Just $ Issue "" 2 (Just "blah") [Tag "fixme"]) it "doesn't parse tags non separated by a space" $ sp [] issue "\ntodo blah[f]\n" `shouldBe` (Just $ Issue "" 2 (Just "blah[f]") []) it "does parse an empty todo" $ sp [] issue "\ntodo\n" `shouldBe` (Just $ Issue "" 2 Nothing []) it "does parse an empty fixme" $ sp [] issue "\nfixme \n" `shouldBe` (Just $ Issue "" 2 Nothing [Tag "fixme"]) it "does parse an empty todo + tags" $ sp [] issue "\ntodo [alfa]\n" `shouldBe` (Just $ Issue "" 2 Nothing [Tag "alfa"]) it "does parse tags before description" $ sp [] issue "\ntodo [alfa] beta\n" `shouldBe` (Just $ Issue "" 2 (Just "beta") [Tag "alfa"]) describe "issues" $ do it "parses multiple issues" $ sp [] issues "\nTODO: this is it [f:w]\n TODO: hey [t]" `shouldBe` Just [Issue "" 2 (Just "this is it") [Tag "f:w"], Issue "" 3 (Just "hey") [Tag "t"]] it "doesn't parse multiple issues if on the same line" $ sp [] issues "\nTODO: this is it [f:w] TODO: hey [t]" `shouldBe` Just [Issue "" 2 (Just "this is it") [Tag "f:w"]] it "parses two issues, tagless, if the second starts on nl" $ sp [] issues "\nTODO: this is it \n todo hey [t]" `shouldBe` Just [Issue "" 2 (Just "this is it") [], Issue "" 3 (Just "hey") [Tag "t"]] it "doesn't pick issues in the middle of a sentence" $ sp [] issues "\nthis is not a todo as you can see" `shouldBe` Just []