{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecursiveDo #-} {-# LANGUAGE ExtendedDefaultRules #-} -- | Test suite for Lucid. module Main where import Lucid import Lucid.Base import Control.Applicative import Control.Monad.State.Strict import qualified Data.Text as T import Test.HUnit import Test.Hspec -- | Test suite entry point, returns exit failure if any test fails. main :: IO () main = hspec spec -- | Test suite. spec :: Spec spec = do describe "text" testText describe "elements" testElements describe "attributes" testAttributes describe "special-elements" testSpecials describe "self-closing" testSelfClosing (==?*) :: (Eq a, Show a) => a -> [a] -> Assertion x ==?* xs | x `elem` xs = return () | otherwise = assertFailure $ show x ++ " is not equal to any of " ++ show xs -- | Test text/unicode. testText :: Spec testText = do it "simple" (renderText "foo" `shouldBe` "foo") it "escaping" (renderText "'<>" `shouldBe` "'<>") it "unicode" (renderText "fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381" `shouldBe` "fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381") -- | Test basic elements and nesting. testElements :: Spec testElements = do it "simple" (renderText (p_ "foo") `shouldBe` "

foo

") it "escaping" (renderText (p_ "'<>") `shouldBe` "

'<>

") it "unicode" (renderText (p_ "fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381") `shouldBe` ("

fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381

")) it "nesting" (renderText (p_ (p_ "Hello!")) `shouldBe` "

Hello!

") it "empty" (renderText (p_ (p_ "")) `shouldBe` "

") it "mixed" (renderText (p_ (style_ "")) `shouldBe` "

") it "no closing" (renderText (p_ (input_ [])) `shouldBe` "

") -- | Test that attribute assigning works properly. testAttributes :: Spec testAttributes = do it "simple" (renderText (p_ [class_ "foo"] "foo") `shouldBe` "

foo

") it "simple raw" (renderText (p_ [style_ "background-image: url('foo')"] "foo") `shouldBe` "

foo

") it "simple raw (href)" (renderText (p_ [onclick_ "window.location.href='asdf';"] "foo") `shouldBe` "

foo

") it "duplicates (class)" (renderText (p_ [class_ "foo", class_ "bar"] "foo") `shouldBe` "

foo

") it "duplicates (id)" (renderText (p_ [id_ "foo", id_ "bar"] "foo") `shouldBe` "

foo

") it "duplicates (style)" (renderText (p_ [style_ "foo", style_ "bar"] "foo") `shouldBe` "

foo

") it "escaping" (renderText (p_ [class_ "foo"] "'<>") `shouldBe` "

'<>

") it "unicode" (renderText (p_ [class_ "foo"] "fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381") `shouldBe` ("

fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381

")) it "nesting" (renderText (p_ [class_ "foo"] (p_ "Hello!")) `shouldBe` "

Hello!

") it "empty" (renderText (p_ [class_ "foo"] (p_ "")) `shouldBe` "

") it "mixed" $ renderText (p_ [class_ "foo",style_ "attrib"] (do style_ "" style_ "")) ==?* [ "

" , "

" ] it "no closing" (renderText (p_ [class_ "foo"] (input_ [])) `shouldBe` "

") it "multiple" $ renderText (p_ [class_ "foo",id_ "zot"] "foo") ==?* [ "

foo

" , "

foo

" ] it "encoded" (renderText (p_ [class_ "foo<>"] "foo") `shouldBe` "

foo

") -- | Test special elements that do something different to normal -- elements. testSpecials :: Spec testSpecials = do it "script" (renderText (script_ "alert('Hello, World!')") `shouldBe` "") it "style" (renderText (style_ "body{background:url('Hello, World!')}") `shouldBe` "") -- | Elements which do not contain children. testSelfClosing :: Spec testSelfClosing = do it "br" (renderText (br_ []) `shouldBe` "
") it "hr" (renderText (hr_ []) `shouldBe` "
") it "input" (renderText (input_ []) `shouldBe` "") it "input" (renderText (input_ [type_ "text"]) `shouldBe` "")