Safe Haskell | None |
---|---|
Language | GHC2021 |
Skeletest.Internal.TestRunner
Contents
Synopsis
- class MonadIO m => Testable (m :: Type -> Type) where
- runTestable :: m () -> IO TestResult
- context :: String -> m a -> m a
- throwFailure :: AssertionFail -> m a
- data TestResult = TestResult {}
- data TestResultMessage
- testResultPass :: TestResult
- testResultFromAssertionFail :: AssertionFail -> IO TestResult
- testResultFromError :: SomeException -> TestResult
- data AssertionFail = AssertionFail {}
- type FailContext = [Text]
Testable
class MonadIO m => Testable (m :: Type -> Type) where Source #
Methods
runTestable :: m () -> IO TestResult Source #
context :: String -> m a -> m a Source #
Add any context to display if the test fails.
>>>
(code, stdout) <- runCommand ...
>>>
context stdout $ code `shouldBe` ExitSuccess
throwFailure :: AssertionFail -> m a Source #
Instances
Testable IO Source # | |
Defined in Skeletest.Assertions Methods runTestable :: IO () -> IO TestResult Source # context :: String -> IO a -> IO a Source # throwFailure :: AssertionFail -> IO a Source # | |
Testable PropertyM Source # | |
Defined in Skeletest.Prop.Internal Methods runTestable :: PropertyM () -> IO TestResult Source # context :: String -> PropertyM a -> PropertyM a Source # throwFailure :: AssertionFail -> PropertyM a Source # |
TestResult
data TestResult Source #
Constructors
TestResult | |
Fields |
data TestResultMessage Source #
AssertionFail
data AssertionFail Source #
Constructors
AssertionFail | |
Fields |
Instances
Exception AssertionFail Source # | |
Defined in Skeletest.Internal.TestRunner Methods toException :: AssertionFail -> SomeException # fromException :: SomeException -> Maybe AssertionFail # displayException :: AssertionFail -> String # backtraceDesired :: AssertionFail -> Bool # | |
Show AssertionFail Source # | |
Defined in Skeletest.Internal.TestRunner Methods showsPrec :: Int -> AssertionFail -> ShowS # show :: AssertionFail -> String # showList :: [AssertionFail] -> ShowS # |
type FailContext = [Text] Source #
Context for failures, in order of most recently added -> least recently added