{-# LANGUAGE OverloadedStrings #-} import Test.Hspec import Text.Markdown import Data.Text.Lazy (Text, unpack, snoc, fromStrict) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Text.Blaze.Html.Renderer.Text (renderHtml) import Control.Monad (forM_) import qualified Data.Set as Set import qualified Data.Map as Map import qualified Filesystem.Path.CurrentOS as F import qualified Filesystem as F import Block import Inline check :: Text -> Text -> Expectation check html md = renderHtml (markdown def md) `shouldBe` html checkSet :: MarkdownSettings -> Text -> Text -> Expectation checkSet set html md = renderHtml (markdown set md) `shouldBe` html check' :: Text -> Text -> Expectation check' html md = renderHtml (markdown def { msXssProtect = False } md) `shouldBe` html checkNoNL :: Text -> Text -> Expectation checkNoNL html md = f (renderHtml $ markdown def { msXssProtect = False } md) `shouldBe` f html where f = TL.filter (/= '\n') -- FIXME add quickcheck: all input is valid main :: IO () main = do examples <- getExamples gruber <- getGruber hspec $ do describe "block" blockSpecs describe "inline" inlineSpecs describe "paragraphs" $ do it "simple" $ check "

Hello World!

" "Hello World!" it "multiline" $ check "

Hello\nWorld!

" "Hello\nWorld!" it "multiple" $ check "

Hello

World!

" "Hello\n\nWorld!" describe "italics" $ do it "simple" $ check "

foo

" "*foo*" it "hanging" $ check "

foo *

" "*foo* *" it "two" $ check "

foo bar

" "*foo* *bar*" describe "italics under" $ do it "simple" $ check "

foo

" "_foo_" it "hanging" $ check "

foo _

" "_foo_ _" it "two" $ check "

foo bar

" "_foo_ _bar_" describe "bold" $ do it "simple" $ check "

foo

" "**foo**" it "hanging" $ check "

foo **

" "**foo** **" it "two" $ check "

foo bar

" "**foo** **bar**" describe "bold under" $ do it "simple" $ check "

foo

" "__foo__" it "hanging" $ check "

foo __

" "__foo__ __" it "two" $ check "

foo bar

" "__foo__ __bar__" describe "html" $ do it "simple" $ check "
Hello
" "
Hello
" it "dangerous" $ check "
Hello
" "
Hello
" it "dangerous and allowed" $ check' "
Hello
" "
Hello
" let ml = "
foo\nbar\nbaz
" it "multiline" $ check ml ml let close = "
foo\nbar\nbaz" it "autoclose" $ check ml close let close2 = "
foo\nbar\nbaz\n\nparagraph" it "autoclose 2" $ check "
foo\nbar\nbaz

paragraph

" close2 describe "inline code" $ do it "simple" $ check "

foo bar baz

" "foo `bar` baz" describe "code block" $ do it "simple" $ check "
foo\n bar\nbaz
" " foo\n bar\n baz" describe "escaping" $ do it "everything" $ check "

*foo_barbaz\\`bin

" "\\*foo\\_bar_baz_\\\\\\`bin" describe "bullets" $ do it "simple" $ check "" "* foo\n* bar\n* baz\n" describe "numbers" $ do it "simple" $ check "
  1. foo
  2. bar
  3. baz
" "5. foo\n2. bar\n1. baz\n" describe "headings" $ do it "hashes" $ check "

foo

bar

baz

" "# foo\n\n## bar\n\n###baz" it "trailing hashes" $ check "

foo

" "# foo ####" it "underline" $ check "

foo

bar

" "foo\n=============\n\nbar\n----------------\n" describe "blockquotes" $ do it "simple" $ check "

foo

bar
" "> foo\n>\n> bar" describe "links" $ do it "simple" $ check "

bar

" "[bar](foo)" it "title" $ check "

bar

" "[bar](foo \"baz\")" it "escaped href" $ check "

bar

" "[bar](foo\\) \"baz\")" it "escaped title" $ check "

bar

" "[bar](foo\\) \"baz\\\"\")" it "inside a paragraph" $ check "

Hello bar World

" "Hello [bar](foo) World" it "not a link" $ check "

Not a [ link

" "Not a [ link" {- describe "github links" $ do it "simple" $ check "

bar

" "[[bar|foo]]" it "no link text" $ check "

foo

" "[[foo]]" it "escaping" $ check "

bar

" "[[bar|foo/baz bin]]" it "inside a list" $ check "" "* [[foo]]" -} describe "images" $ do it "simple" $ check "

\"foo\"

" "![foo](http://link.to/image.jpg)" it "title" $ check "

\"foo\"

" "![foo](http://link.to/image.jpg \"bar\")" it "inside a paragraph" $ check "

Hello \"foo\" World

" "Hello ![foo](http://link.to/image.jpg) World" it "not an image" $ check "

Not an ![ image

" "Not an ![ image" describe "rules" $ do let options = concatMap (\t -> [t, snoc t '\n']) [ "* * *" , "***" , "*****" , "- - -" , "---------------------------------------" , "----------------------------------" ] forM_ options $ \o -> it (unpack o) $ check "
" o describe "html" $ do it "inline" $ check "

foo
bar

" "foo
bar" it "inline xss" $ check "

foo
bar

" "foo
bar" it "block" $ check "
hello world
" "
hello world
" it "block xss" $ check "alert('evil')" "" it "should be escaped" $ check "

1 < 2

" "1 < 2" it "standalone" $ checkSet def { msStandaloneHtml = Set.fromList ["", ""], msXssProtect = False } "
foo\nbar
" "\n```haskell\nfoo\nbar\n```\n\n" describe "fencing" $ do it "custom fencing" $ checkSet def { msFencedHandlers = Map.union (htmlFencedHandler "@@@" (\clazz -> T.concat ["
"]) (const "
")) (msFencedHandlers def) } "

foo

bar

" "@@@ someclass\nfoo\n\n> bar\n@@@" describe "examples" $ sequence_ examples describe "John Gruber's test suite" $ sequence_ gruber getExamples :: IO [Spec] getExamples = do files <- F.listDirectory "test/examples" mapM go $ filter (flip F.hasExtension "md") files where go fp = do input <- F.readTextFile fp output <- F.readTextFile $ F.replaceExtension fp "html" return $ it (F.encodeString $ F.basename fp) $ check (fromStrict $ T.strip output) (fromStrict input) getGruber :: IO [Spec] getGruber = do files <- F.listDirectory "test/Tests" mapM go $ filter (flip F.hasExtension "text") files where go fp = do input <- F.readTextFile fp output <- F.readTextFile $ F.replaceExtension fp "html" return $ it (F.encodeString $ F.basename fp) $ checkNoNL (fromStrict $ T.strip output) (fromStrict input)