{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
module Web.Api.WebDriver.Assert (
Assertion()
, success
, failure
, AssertionStatement(..)
, AssertionComment(..)
, AssertionResult()
, isSuccess
, printAssertion
, Assert(..)
, AssertionSummary(..)
, summarize
, summarizeAll
, printSummary
, assertSuccessIf
, assertSuccess
, assertFailure
, assertTrue
, assertFalse
, assertEqual
, assertNotEqual
, assertIsSubstring
, assertIsNotSubstring
, assertIsNamedSubstring
, assertIsNotNamedSubstring
) where
import Data.List
( unwords, isInfixOf )
import Data.String
( IsString, fromString )
import Test.QuickCheck
( Arbitrary(..) )
data Assertion = Assertion
{ assertionStatement :: AssertionStatement
, assertionComment :: AssertionComment
, assertionResult :: AssertionResult
} deriving (Eq, Show)
newtype AssertionStatement = AssertionStatement
{ theAssertionStatement :: String
} deriving Eq
instance Show AssertionStatement where
show = theAssertionStatement
instance IsString AssertionStatement where
fromString = AssertionStatement
instance Arbitrary AssertionStatement where
arbitrary = AssertionStatement <$> arbitrary
newtype AssertionComment = AssertionComment
{ theAssertionComment :: String
} deriving Eq
instance Show AssertionComment where
show = theAssertionComment
instance IsString AssertionComment where
fromString = AssertionComment
instance Arbitrary AssertionComment where
arbitrary = AssertionComment <$> arbitrary
data AssertionResult
= AssertSuccess | AssertFailure
deriving (Eq, Show)
instance Arbitrary AssertionResult where
arbitrary = do
p <- arbitrary
return $ if p then AssertSuccess else AssertFailure
isSuccess :: Assertion -> Bool
isSuccess a = AssertSuccess == assertionResult a
printAssertion :: Assertion -> String
printAssertion Assertion{..} =
case assertionResult of
AssertSuccess ->
unwords
[ "\x1b[1;32mValid Assertion\x1b[0;39;49m"
, "\nassertion: " ++ show assertionStatement
, "\ncomment: " ++ show assertionComment
]
AssertFailure ->
unwords
[ "\x1b[1;31mInvalid Assertion\x1b[0;39;49m"
, "\nassertion: " ++ show assertionStatement
, "\ncomment: " ++ show assertionComment
]
success
:: AssertionStatement
-> AssertionComment
-> Assertion
success statement comment = Assertion
{ assertionStatement = statement
, assertionComment = comment
, assertionResult = AssertSuccess
}
failure
:: AssertionStatement
-> AssertionComment
-> Assertion
failure statement comment = Assertion
{ assertionStatement = statement
, assertionComment = comment
, assertionResult = AssertFailure
}
class Assert m where
assert :: Assertion -> m ()
assertSuccessIf
:: (Monad m, Assert m)
=> Bool
-> AssertionStatement
-> AssertionComment
-> m ()
assertSuccessIf p statement comment =
assert $ (if p then success else failure) statement comment
assertSuccess
:: (Monad m, Assert m)
=> AssertionComment
-> m ()
assertSuccess = assertSuccessIf True (AssertionStatement "Success!")
assertFailure
:: (Monad m, Assert m)
=> AssertionComment
-> m ()
assertFailure = assertSuccessIf False (AssertionStatement "Failure :(")
assertTrue
:: (Monad m, Assert m)
=> Bool
-> AssertionComment
-> m ()
assertTrue p = assertSuccessIf p
(AssertionStatement $ show p ++ " is True")
assertFalse
:: (Monad m, Assert m)
=> Bool
-> AssertionComment
-> m ()
assertFalse p = assertSuccessIf (not p)
(AssertionStatement $ show p ++ " is False")
assertEqual
:: (Monad m, Assert m, Eq t, Show t)
=> t
-> t
-> AssertionComment
-> m ()
assertEqual x y = assertSuccessIf (x == y)
(AssertionStatement $ show x ++ " is equal to " ++ show y)
assertNotEqual
:: (Monad m, Assert m, Eq t, Show t)
=> t
-> t
-> AssertionComment
-> m ()
assertNotEqual x y = assertSuccessIf (x /= y)
(AssertionStatement $ show x ++ " is not equal to " ++ show y)
assertIsSubstring
:: (Monad m, Assert m, Eq a, Show a)
=> [a]
-> [a]
-> AssertionComment
-> m ()
assertIsSubstring x y = assertSuccessIf (x `isInfixOf` y)
(AssertionStatement $ show x ++ " is a substring of " ++ show y)
assertIsNotSubstring
:: (Monad m, Assert m, Eq a, Show a)
=> [a]
-> [a]
-> AssertionComment
-> m ()
assertIsNotSubstring x y = assertSuccessIf (not $ x `isInfixOf` y)
(AssertionStatement $ show x ++ " is not a substring of " ++ show y)
assertIsNamedSubstring
:: (Monad m, Assert m, Eq a, Show a)
=> [a]
-> ([a],String)
-> AssertionComment
-> m ()
assertIsNamedSubstring x (y,name) = assertSuccessIf (x `isInfixOf` y)
(AssertionStatement $ show x ++ " is a substring of " ++ name)
assertIsNotNamedSubstring
:: (Monad m, Assert m, Eq a, Show a)
=> [a]
-> ([a],String)
-> AssertionComment
-> m ()
assertIsNotNamedSubstring x (y,name) = assertSuccessIf (not $ isInfixOf x y)
(AssertionStatement $ show x ++ " is not a substring of " ++ name)
data AssertionSummary = AssertionSummary
{ numSuccesses :: Integer
, numFailures :: Integer
, failures :: [Assertion]
, successes :: [Assertion]
} deriving (Eq, Show)
instance Semigroup AssertionSummary where
x <> y = AssertionSummary
{ numSuccesses = numSuccesses x + numSuccesses y
, numFailures = numFailures x + numFailures y
, failures = failures x ++ failures y
, successes = successes x ++ successes y
}
instance Monoid AssertionSummary where
mempty = AssertionSummary 0 0 [] []
mappend = (<>)
summary :: Assertion -> AssertionSummary
summary x = AssertionSummary
{ numSuccesses = if isSuccess x then 1 else 0
, numFailures = if isSuccess x then 0 else 1
, failures = if isSuccess x then [] else [x]
, successes = if isSuccess x then [x] else []
}
summarize :: [Assertion] -> AssertionSummary
summarize = mconcat . map summary
summarizeAll :: [AssertionSummary] -> AssertionSummary
summarizeAll = mconcat
printSummary :: AssertionSummary -> IO ()
printSummary AssertionSummary{..} = do
mapM_ (putStrLn . printAssertion) failures
putStrLn $ "Assertions: " ++ show (numSuccesses + numFailures)
putStrLn $ "Failures: " ++ show numFailures
numAssertions :: AssertionSummary -> Integer
numAssertions x = numSuccesses x + numFailures x