{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module MarkdownSpec (tests) where
import BasePrelude
-- Lenses
import Lens.Micro.Platform
-- Text
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Text (Text)
-- HTML
import Text.HTML.TagSoup hiding (sections)
import Lucid (ToHtml, toHtml, renderText)
-- Markdown
import CMark hiding (Node)
import qualified CMark as MD (Node(..))
import CMark.Sections
import Data.Tree
-- Testing
import Test.Hspec
import Guide.Markdown
tests :: Spec
tests = describe "Markdown" $ do
allMarkdowns $ \convert -> do
it "has mdSource filled accurately" $ do
for_ mdBlockExamples $ \s ->
s `shouldBe` fst (convert s)
it "only has allowed tags" $ do
for_ mdBlockExamples $ \s -> do
let html = snd (convert s)
let badTags = getTags html \\ (inlineTags ++ blockTags)
unless (null badTags) $ expectationFailure $
printf "%s got rendered as %s, but some tags (%s) are disallowed"
(show s) (show html) (T.intercalate "," badTags)
it "doesn't pass bad HTML through" $ do
let s = ""
let html = snd (convert s)
when ("script" `elem` getTags html) $ expectationFailure $
printf "%s got rendered as %s, but the