-- | A whole bunch of simple test cases -- {-# LANGUAGE OverloadedStrings #-} module Text.Blaze.Html.Tests ( tests ) where import Prelude hiding (div, id) import Control.Monad (forM_) import Data.Monoid (mempty, mappend, mconcat) import Data.Text (Text) import Test.HUnit ((@=?)) import Test.Framework.Providers.HUnit (testCase) import Test.Framework (Test) import qualified Data.ByteString.Lazy.Char8 as LBC import Text.Blaze.Html.Tests.Util import Text.Blaze.Html5 hiding (map) import Text.Blaze.Html5.Attributes import Text.Blaze.Internal import qualified Text.Blaze.Html5 as H -- | Type for a simple HTML test. This data type contains the expected output -- and the HTML template. -- data HtmlTest = HtmlTest LBC.ByteString Html -- | Create tests from an HTML test -- makeTests :: String -> HtmlTest -> [Test] makeTests baseName (HtmlTest expected h) = [ testCase (baseName ++ " (String)") $ expected @=? renderUsingString h , testCase (baseName ++ " (Text)") $ expected @=? renderUsingText h , testCase (baseName ++ " (Utf8)") $ expected @=? renderUsingUtf8 h ] -- | Actual tests -- tests :: [Test] tests = concatMap (uncurry makeTests) $ zip names -- Simple cases [ HtmlTest "

banana

banana
" $ div ! id "foo" $ do p "banana" H.span "banana" , HtmlTest "\"bar\"" $ img ! src "foo.png" ! alt "bar" -- Escaping cases , HtmlTest ""&"" "\"&\"" , HtmlTest "<img>" $ toHtml ("" :: Text) , HtmlTest ""'"" "\"'\"" , HtmlTest "" $ img ! src "&" , HtmlTest "hello" $ H.u "hello" -- Pre-escaping cases , HtmlTest "<3 Haskell" $ preEscapedToMarkup ("<3 Haskell" :: String) , HtmlTest "