{-# LANGUAGE OverloadedStrings #-} module Web.Slack.MessageParserSpec (spec) where -- hspec import Test.Hspec -- slack-web import Web.Slack.MessageParser import Web.Slack.Types -- text import Data.Text (Text) testGetUserDesc :: UserId -> Text testGetUserDesc (UserId "USER1") = "user_one" testGetUserDesc x = unUserId x testHtmlRenderers :: HtmlRenderers testHtmlRenderers = HtmlRenderers { emoticonRenderer = \x -> ":>" <> x <> "<:" } msgToHtml :: Text -> Text msgToHtml = messageToHtml testHtmlRenderers testGetUserDesc . SlackMessageText spec :: Spec spec = describe "message contents parsing" $ do it "handles the trivial case well" $ msgToHtml "hello" `shouldBe` "hello" it "converts a simple message to HTML correctly" $ msgToHtml "_hello_ *world* `code` ```longer\ncode```" `shouldBe` "hello world google code
longer\ncode
" it "degrades properly to return the input message if it's incorrect" $ msgToHtml "link not closed both" it "aborts nicely on interspersed bold & italics" $ msgToHtml "inter *sper_ *sed_" `shouldBe` "inter *sper_ *sed_" it "parses blockquotes properly" $ msgToHtml "look at this:\n> test *wow*" `shouldBe` "look at this:
test wow
" it "parses code blocks properly" $ msgToHtml "look at this:\n```test *wow*```" `shouldBe` "look at this:
test *wow*
" it "handles non-italics underscores in text well" $ -- need to put other HTML symbols, otherwise if the parsing fails -- i won't find out since we default to returning the input on -- parsing failure msgToHtml "a:\n>b.\n:slightly_smiling_face:" `shouldBe` "a:
b.
:>slightly_smiling_face<:" it "properly parses multiline blockquotes" $ msgToHtml "> first row\n> second row\nthird row\n> fourth row" `shouldBe` "
first row
second row
third row
fourth row
" it "converts usernames" $ msgToHtml "<@USER1> should be converted, <@USER1|default> stay default" `shouldBe` "@user_one should be converted, @default stay default" it "converts carriage returns" $ msgToHtml "a\nb" `shouldBe` "a
b" it "handles full stops as punctuation" $ msgToHtml "*b*." `shouldBe` "b."