#if MIN_VERSION_base(4,8,1)
#define HAS_SOURCE_LOCATIONS
#endif
module Test.HUnit.Lang (
Assertion,
assertFailure,
Location (..),
Result (..),
performTestCase,
HUnitFailure (..)
) where
import Control.DeepSeq
import Control.Exception as E
import Data.Typeable
#ifdef HAS_SOURCE_LOCATIONS
import GHC.SrcLoc
import GHC.Stack
#endif
type Assertion = IO ()
data Location = Location {
locationFile :: FilePath
, locationLine :: Int
, locationColumn :: Int
} deriving (Eq, Ord, Show)
data HUnitFailure = HUnitFailure (Maybe Location) String
deriving (Eq, Ord, Show, Typeable)
instance Exception HUnitFailure
assertFailure ::
#ifdef HAS_SOURCE_LOCATIONS
(?loc :: CallStack) =>
#endif
String
-> Assertion
assertFailure msg = msg `deepseq` E.throwIO (HUnitFailure location msg)
where
location :: Maybe Location
#ifdef HAS_SOURCE_LOCATIONS
location = case reverse (getCallStack ?loc) of
(_, loc) : _ -> Just $ Location (srcLocFile loc) (srcLocStartLine loc) (srcLocStartCol loc)
[] -> Nothing
#else
location = Nothing
#endif
data Result = Success | Failure (Maybe Location) String | Error (Maybe Location) String
deriving (Eq, Ord, Show)
performTestCase :: Assertion
-> IO Result
performTestCase action =
(action >> return Success)
`E.catches`
[E.Handler (\(HUnitFailure loc msg) -> return $ Failure loc msg),
E.Handler (\e -> throw (e :: E.AsyncException)),
E.Handler (\e -> return $ Error Nothing $ show (e :: E.SomeException))]