{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE DataKinds #-} module Main where import Html import qualified Html.Attribute as A import Data.Proxy import Test.Hspec import Test.QuickCheck import Data.Text.Lazy.Encoding import qualified Data.Text.Lazy as T newtype Escaped = Escaped String deriving Show instance Arbitrary Escaped where arbitrary = Escaped <$> arbitrary `suchThat` (\x -> all (`notElem` x) "<>&\"'") main :: IO () main = hspec spec spec :: Spec spec = let allT a b c = b (renderString a, T.unpack $ renderText a, T.unpack . decodeUtf8 $ renderByteString a) (c, c, c) in parallel $ do describe "render" $ do it "is id on strings without escaping chars" $ do property $ \(Escaped x) -> allT x (==) x it "handles single elements" $ do property $ \(Escaped x) -> allT (div_ x) (==) ("
" ++ x ++ "
") it "handles nested elements" $ do property $ \(Escaped x) -> allT (div_ (div_ x)) (==) ("
" ++ x ++ "
") it "handles parallel elements" $ do property $ \(Escaped x) (Escaped y) -> allT (div_ x # div_ y) (==) ("
" ++ x ++ "
" ++ y ++ "
") it "doesn't use closing tags for empty elements" $ do allT area_ shouldBe "" allT base_ shouldBe "" allT br_ shouldBe "
" allT col_ shouldBe "" allT embed_ shouldBe "" allT hr_ shouldBe "
" allT iframe_ shouldBe "