{-# LANGUAGE TypeApplications #-} {-# 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 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` "