{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE ExtendedDefaultRules #-} -- | Test suite for ACE. module Main where import Lucid 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 testText :: Spec testText = do it "simple" (renderText "foo" == "foo") it "escaping" (renderText "'<>" == "'<>") it "unicode" (renderText "fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381" == "fo\243o\333o(\4326\728\8995\728\4326) \9835\65381*:.\65377. .\65377.:*\65381") testElements :: Spec testElements = do it "simple" (renderText (p_ "foo") == "

foo

") it "escaping" (renderText (p_ "'<>") == "

'<>

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

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

")) it "nesting" (renderText (p_ (p_ "Hello!")) == "

Hello!

") it "empty" (renderText (p_ (p_ "")) == "

") it "mixed" (renderText (p_ (style_ "")) == "

") it "no closing" (renderText (p_ input_) == "

") testAttributes :: Spec testAttributes = do it "simple" (renderText (with p_ [class_ "foo"] "foo") == "

foo

") it "escaping" (renderText (with p_ [class_ "foo"] "'<>") == "

'<>

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

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

")) it "nesting" (renderText (with p_ [class_ "foo"] (p_ "Hello!")) == "

Hello!

") it "empty" (renderText (with p_ [class_ "foo"] (p_ "")) == "

") it "mixed" (renderText (with p_ [class_ "foo"] (style_ "")) == "

") it "no closing" (renderText (with p_ [class_ "foo"] input_) == "

") it "multiple" (renderText (with p_ [class_ "foo",id_ "zot"] "foo") == "

foo

") it "encoded" (renderText (with p_ [class_ "foo<>"] "foo") == "

foo

") it "nesting attributes" (renderText (with (with p_ [class_ "foo"]) [class_ "bar"] "foo") == "

foo

")