{-# LANGUAGE OverloadedStrings, FlexibleInstances, TypeSynonymInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Text.Blaze.Tests ( tests ) where import Prelude hiding (div, id) import Data.Monoid (mempty) import Control.Monad (replicateM) import Control.Applicative ((<$>)) import Data.Word (Word8) import Data.Char (ord) import Data.List (isInfixOf) import Test.Framework (Test) import Test.HUnit (Assertion, (@=?)) import Test.Framework.Providers.HUnit (testCase) import Test.Framework.Providers.QuickCheck2 (testProperty) import Test.QuickCheck import qualified Data.ByteString as SB import qualified Data.ByteString.Lazy as LB import qualified Data.ByteString.Lazy.Char8 as LBC import Text.Blaze.Internal import Text.Blaze.Tests.Util tests :: [Test] tests = [ testProperty "left identity Monoid law" monoidLeftIdentity , testProperty "right identity Monoid law" monoidRightIdentity , testProperty "associativity Monoid law" monoidAssociativity , testProperty "mconcat Monoid law" monoidConcat , testProperty "post escaping characters" postEscapingCharacters , testProperty "valid UTF-8" isValidUtf8 , testProperty "external " wellNestedBrackets , testProperty "unsafeByteString id" unsafeByteStringId , testCase "conditional attributes" conditionalAttributes , testCase "contents 1" contents1 ] -- | The left identity Monoid law. -- monoidLeftIdentity :: Markup -> Bool monoidLeftIdentity h = (return () >> h) == h -- | The right identity Monoid law. -- monoidRightIdentity :: Markup -> Bool monoidRightIdentity h = (h >> return ()) == h -- | The associativity Monoid law. -- monoidAssociativity :: Markup -> Markup -> Markup -> Bool monoidAssociativity x y z = (x >> (y >> z)) == ((x >> y) >> z) -- | Concatenation Monoid law. -- monoidConcat :: [Markup] -> Bool monoidConcat xs = sequence_ xs == foldr (>>) (return ()) xs -- | Escaped content cannot contain certain characters. -- postEscapingCharacters :: String -> Bool postEscapingCharacters str = LB.all (`notElem` forbidden) $ renderUsingUtf8 (string str) where forbidden = map (fromIntegral . ord) "\"'<>" -- | Check if the produced bytes are valid UTF-8 -- isValidUtf8 :: Markup -> Bool isValidUtf8 = isValidUtf8' . LB.unpack . renderUsingUtf8 where isIn x y z = (x <= z) && (z <= y) isValidUtf8' :: [Word8] -> Bool isValidUtf8' [] = True isValidUtf8' (x:t) -- One byte | isIn 0x00 0x7f x = isValidUtf8' t -- Two bytes | isIn 0xc0 0xdf x = case t of (y:t') -> isIn 0x80 0xbf y && isValidUtf8' t' _ -> False -- Three bytes | isIn 0xe0 0xef x = case t of (y:z:t') -> all (isIn 0x80 0xbf) [y, z] && isValidUtf8' t' _ -> False -- Four bytes | isIn 0xf0 0xf7 x = case t of (y:z:u:t') -> all (isIn 0x80 0xbf) [y, z, u] && isValidUtf8' t' _ -> False | otherwise = False -- | Rendering an unsafe bytestring should not do anything -- unsafeByteStringId :: [Word8] -> Bool unsafeByteStringId ws = LB.pack ws == renderUsingUtf8 (unsafeByteString $ SB.pack ws) -- | Check if the "@ or @