{-# LANGUAGE CPP #-}
module Test.Framework.AssertM (
AssertM(..), AssertStackElem(..), AssertBool(..), boolValue, eitherValue, formatStack
) where
import Data.Maybe
import qualified Data.Text as T
import Control.Applicative (Applicative(..))
import Control.Monad (liftM, ap)
import Test.Framework.TestInterface
import Test.Framework.Location
import Test.Framework.Colors
class Monad m => AssertM m where
genericAssertFailure__ :: Location -> ColorString -> m a
genericSubAssert :: Location -> Maybe String -> m a -> m a
instance AssertM IO where
genericAssertFailure__ loc s = failHTF (FullTestResult (Just loc) [] (Just s) (Just Fail))
genericSubAssert loc mMsg action = subAssertHTF loc mMsg action
data AssertStackElem
= AssertStackElem
{ ase_message :: Maybe String
, ase_location :: Maybe Location
}
deriving (Eq, Ord, Show, Read)
data AssertBool a
= AssertOk a
| AssertFailed [AssertStackElem]
deriving (Eq, Ord, Show, Read)
instance Functor AssertBool where
fmap = liftM
instance Applicative AssertBool where
pure = return
(<*>) = ap
instance Monad AssertBool where
return = AssertOk
AssertFailed stack >>= _ = AssertFailed stack
AssertOk x >>= k = k x
#if !(MIN_VERSION_base(4,13,0))
fail msg = AssertFailed [AssertStackElem (Just msg) Nothing]
#endif
instance AssertM AssertBool where
genericAssertFailure__ loc s =
AssertFailed [AssertStackElem (Just (T.unpack $ renderColorString s False)) (Just loc)]
genericSubAssert loc mMsg action =
case action of
AssertOk x -> AssertOk x
AssertFailed stack ->
AssertFailed (AssertStackElem mMsg (Just loc) : stack)
boolValue :: AssertBool a -> Bool
boolValue x =
case x of
AssertOk _ -> True
AssertFailed _ -> False
eitherValue :: AssertBool a -> Either String a
eitherValue x =
case x of
AssertOk z -> Right z
AssertFailed stack -> Left (formatStack stack)
formatStack :: [AssertStackElem] -> String
formatStack stack =
unlines $ map formatStackElem $ zip [0..] $ reverse stack
where
formatStackElem (pos, AssertStackElem mMsg mLoc) =
let floc = fromMaybe "<unknown location>" $ fmap showLoc mLoc
fmsg = fromMaybe "" $ fmap (\s -> ": " ++ s) mMsg
pref = if pos > 0 then " called from " else ""
in pref ++ floc ++ fmsg