{-# LANGUAGE OverloadedStrings #-} import Text.Blaze.Html (toHtml) import Text.Blaze.Html5 (figure) import Test.Hspec import Text.Markdown import Data.Text.Lazy (Text, unpack, snoc, fromStrict) import qualified Data.Text as T import qualified Data.Text.IO as TIO 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 Data.List (isInfixOf, isSuffixOf) import Data.Maybe (fromMaybe) import Data.CallStack import System.Directory (getDirectoryContents) import System.FilePath ((), replaceExtension) import Block import Inline check :: HasCallStack => 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 "line break" $ do it "is inserted for a single newline after two spaces" $ check "

Hello
World!

" "Hello \nWorld!" it "is also inserted for a single CRLF after two spaces" $ check "

Hello
World!

" "Hello \r\nWorld!" it "preserves quote nesting of the previous line" $ check "

Q1
Q2

P2

" "> Q1 \nQ2\n\nP2" it "consumes all trailing whitespace on the previous line" $ check "

Hello
World!

" "Hello \nWorld!" 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" it "custom renderer" $ checkSet def { msBlockCodeRenderer = (\_ (u,_) -> figure (toHtml u)) } "
foo\n bar\nbaz
" "```haskell\nfoo\n bar\nbaz\n```" 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 "headings with ID" $ do let withHeadingId = def { msAddHeadingId = True } it "without spaces" $ checkSet withHeadingId "

foo

bar

baz

" "# foo\n\n## bar\n\n###baz" it "with spaces" $ checkSet withHeadingId "

Executive summary

" "# Executive summary" it "with special characters" $ checkSet withHeadingId "

Executive summary .!@#$%^*()-_=:

" "# Executive summary .!@#$%^*()-_=:" 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" it "new tab" $ checkSet def { msLinkNewTab = True } "

bar

" "[bar](foo)" {- 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 "footnotes" $ do it "inline" $ check "

[1]hello

" "{1}hello" it "references" $ check "

[1]hello

" "{^1}hello" describe "examples" $ sequence_ examples describe "John Gruber's test suite" $ sequence_ gruber it "comments without spaces #22" $ check "" "" describe "no follow" $ do it "external 1" $ checkSet (setNoFollowExternal def) "

example

" "[example](http://example.com)" it "external 2" $ checkSet (setNoFollowExternal def) "

example

" "[example](//example.com)" it "internal" $ checkSet (setNoFollowExternal def) "

example

" "[example](/foo)" getExamples :: IO [Spec] getExamples = do files <- getDirectoryContents dir mapM go $ filter (".md" `isSuffixOf`) files where dir = "test/examples" go basename = do let fp = dir basename input <- TIO.readFile fp output <- TIO.readFile $ replaceExtension fp "html" let (checker, stripper) | "-spec" `isInfixOf` fp = (check', dropFinalLF) | otherwise = (check, T.strip) return $ it basename $ checker (fromStrict $ stripper output) (fromStrict input) dropFinalLF t = fromMaybe t $ T.stripSuffix "\n" t getGruber :: IO [Spec] getGruber = do files <- getDirectoryContents dir mapM go $ filter (".text" `isSuffixOf`) files where dir = "test/Tests" go basename = do let fp = dir basename input <- TIO.readFile fp output <- TIO.readFile $ replaceExtension fp "html" return $ it basename $ checkNoNL (fromStrict $ T.strip output) (fromStrict input)