{-# LANGUAGE TypeApplications #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE DataKinds #-} module Main where import Html import Data.Proxy import Test.Hspec import Test.QuickCheck import Custom main :: IO () main = hspec spec spec :: Spec spec = parallel $ do describe "render" $ do it "is id on strings without escaping" $ do property $ \x -> renderString (Raw x) === x it "handles single elements" $ do property $ \x -> renderString (Div :> Raw x) === "
" ++ x ++ "
" it "handles nested elements" $ do property $ \x -> renderString (Div :> Div :> Raw x) === "
" ++ x ++ "
" it "handles parallel elements" $ do property $ \x y -> renderString (Div :> Raw x # Div :> Raw y) === "
" ++ x ++ "
" ++ y ++ "
" it "doesn't use closing tags for empty elements" $ do renderString Area `shouldBe` "" renderString Base `shouldBe` "" renderString Br `shouldBe` "
" renderString Col `shouldBe` "" renderString Embed `shouldBe` "" renderString Hr `shouldBe` "
" renderString Iframe `shouldBe` "