Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Syd.Run
Description
This module defines the IsTest
class and the different instances for it.
Synopsis
- class IsTest e where
- type Arg1 e
- type Arg2 e
- runTest :: e -> TestRunSettings -> ((Arg1 e -> Arg2 e -> IO ()) -> IO ()) -> IO TestRunResult
- runPureTestWithArg :: (outerArgs -> innerArg -> Bool) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult
- applyWrapper2 :: forall r outerArgs innerArg. ((outerArgs -> innerArg -> IO ()) -> IO ()) -> (outerArgs -> innerArg -> IO r) -> IO (Either (Either String Assertion) r)
- runIOTestWithArg :: (outerArgs -> innerArg -> IO ()) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult
- runPropertyTestWithArg :: (outerArgs -> innerArg -> Property) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult
- aroundProperty :: ((a -> b -> IO ()) -> IO ()) -> (a -> b -> Property) -> Property
- aroundProp :: ((a -> b -> IO ()) -> IO ()) -> (a -> b -> Prop) -> Prop
- aroundRose :: ((a -> b -> IO ()) -> IO ()) -> (a -> b -> Rose Result) -> Rose Result
- data GoldenTest a = GoldenTest {
- goldenTestRead :: IO (Maybe a)
- goldenTestProduce :: IO a
- goldenTestWrite :: a -> IO ()
- goldenTestCompare :: a -> a -> Maybe Assertion
- runGoldenTestWithArg :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult
- exceptionHandlers :: [Handler (Either (Either String Assertion) a)]
- type Test = IO ()
- data TestRunSettings = TestRunSettings {}
- defaultTestRunSettings :: TestRunSettings
- data TestRunResult = TestRunResult {
- testRunResultStatus :: !TestStatus
- testRunResultException :: !(Maybe (Either String Assertion))
- testRunResultNumTests :: !(Maybe Word)
- testRunResultNumShrinks :: !(Maybe Word)
- testRunResultFailingInputs :: [String]
- testRunResultLabels :: !(Maybe (Map [String] Int))
- testRunResultClasses :: !(Maybe (Map String Int))
- testRunResultTables :: !(Maybe (Map String (Map String Int)))
- testRunResultGoldenCase :: !(Maybe GoldenCase)
- testRunResultExtraInfo :: !(Maybe String)
- data TestStatus
- data Assertion
- data GoldenCase
- timeItT :: MonadIO m => m a -> m (Timed a)
- data Timed a = Timed {
- timedValue :: !a
- timedTime :: !Word64
Documentation
Methods
runTest :: e -> TestRunSettings -> ((Arg1 e -> Arg2 e -> IO ()) -> IO ()) -> IO TestRunResult Source #
Instances
IsTest Bool Source # | |
IsTest Property Source # | |
IsTest (IO ()) Source # | |
IsTest (IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run Methods runTest :: IO (GoldenTest a) -> TestRunSettings -> ((Arg1 (IO (GoldenTest a)) -> Arg2 (IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (GoldenTest a) Source # | |
Defined in Test.Syd.Run Methods runTest :: GoldenTest a -> TestRunSettings -> ((Arg1 (GoldenTest a) -> Arg2 (GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run Associated Types type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # Methods runTest :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) -> Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (arg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run Associated Types type Arg1 (arg -> IO (GoldenTest a)) Source # type Arg2 (arg -> IO (GoldenTest a)) Source # Methods runTest :: (arg -> IO (GoldenTest a)) -> TestRunSettings -> ((Arg1 (arg -> IO (GoldenTest a)) -> Arg2 (arg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run Associated Types type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source # type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source # Methods runTest :: (outerArgs -> innerArg -> GoldenTest a) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> GoldenTest a) -> Arg2 (outerArgs -> innerArg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (arg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run Methods runTest :: (arg -> GoldenTest a) -> TestRunSettings -> ((Arg1 (arg -> GoldenTest a) -> Arg2 (arg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> Property) Source # | |
Defined in Test.Syd.Run | |
IsTest (arg -> Property) Source # | |
IsTest (outerArgs -> innerArg -> IO ()) Source # | |
Defined in Test.Syd.Run | |
IsTest (arg -> IO ()) Source # | |
IsTest (outerArgs -> innerArg -> Bool) Source # | |
Defined in Test.Syd.Run | |
IsTest (arg -> Bool) Source # | |
runPureTestWithArg :: (outerArgs -> innerArg -> Bool) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult Source #
applyWrapper2 :: forall r outerArgs innerArg. ((outerArgs -> innerArg -> IO ()) -> IO ()) -> (outerArgs -> innerArg -> IO r) -> IO (Either (Either String Assertion) r) Source #
runIOTestWithArg :: (outerArgs -> innerArg -> IO ()) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult Source #
runPropertyTestWithArg :: (outerArgs -> innerArg -> Property) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult Source #
aroundProp :: ((a -> b -> IO ()) -> IO ()) -> (a -> b -> Prop) -> Prop Source #
aroundRose :: ((a -> b -> IO ()) -> IO ()) -> (a -> b -> Rose Result) -> Rose Result Source #
data GoldenTest a Source #
Constructors
GoldenTest | |
Fields
|
Instances
IsTest (IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run Methods runTest :: IO (GoldenTest a) -> TestRunSettings -> ((Arg1 (IO (GoldenTest a)) -> Arg2 (IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (GoldenTest a) Source # | |
Defined in Test.Syd.Run Methods runTest :: GoldenTest a -> TestRunSettings -> ((Arg1 (GoldenTest a) -> Arg2 (GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run Associated Types type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # Methods runTest :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) -> Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (arg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run Associated Types type Arg1 (arg -> IO (GoldenTest a)) Source # type Arg2 (arg -> IO (GoldenTest a)) Source # Methods runTest :: (arg -> IO (GoldenTest a)) -> TestRunSettings -> ((Arg1 (arg -> IO (GoldenTest a)) -> Arg2 (arg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run Associated Types type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source # type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source # Methods runTest :: (outerArgs -> innerArg -> GoldenTest a) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> GoldenTest a) -> Arg2 (outerArgs -> innerArg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (arg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run Methods runTest :: (arg -> GoldenTest a) -> TestRunSettings -> ((Arg1 (arg -> GoldenTest a) -> Arg2 (arg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
type Arg1 (IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run | |
type Arg1 (GoldenTest a) Source # | |
Defined in Test.Syd.Run | |
type Arg2 (IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run | |
type Arg2 (GoldenTest a) Source # | |
Defined in Test.Syd.Run | |
type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run | |
type Arg1 (arg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run | |
type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run | |
type Arg1 (arg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run | |
type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run | |
type Arg2 (arg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run | |
type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run | |
type Arg2 (arg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run |
runGoldenTestWithArg :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult Source #
data TestRunSettings Source #
Constructors
TestRunSettings | |
Instances
data TestRunResult Source #
Constructors
TestRunResult | |
Fields
|
Instances
data TestStatus Source #
Constructors
TestPassed | |
TestFailed |
Instances
Eq TestStatus Source # | |
Defined in Test.Syd.Run | |
Show TestStatus Source # | |
Defined in Test.Syd.Run Methods showsPrec :: Int -> TestStatus -> ShowS # show :: TestStatus -> String # showList :: [TestStatus] -> ShowS # | |
Generic TestStatus Source # | |
Defined in Test.Syd.Run Associated Types type Rep TestStatus :: Type -> Type # | |
type Rep TestStatus Source # | |
Constructors
Instances
data GoldenCase Source #
Constructors
GoldenNotFound | |
GoldenStarted | |
GoldenReset |
Instances
Eq GoldenCase Source # | |
Defined in Test.Syd.Run | |
Show GoldenCase Source # | |
Defined in Test.Syd.Run Methods showsPrec :: Int -> GoldenCase -> ShowS # show :: GoldenCase -> String # showList :: [GoldenCase] -> ShowS # | |
Generic GoldenCase Source # | |
Defined in Test.Syd.Run Associated Types type Rep GoldenCase :: Type -> Type # | |
type Rep GoldenCase Source # | |
Defined in Test.Syd.Run type Rep GoldenCase = D1 ('MetaData "GoldenCase" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) (C1 ('MetaCons "GoldenNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GoldenStarted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GoldenReset" 'PrefixI 'False) (U1 :: Type -> Type))) |
timeItT :: MonadIO m => m a -> m (Timed a) Source #
Time an action and return the result as well as how long it took in seconds.
This function does not use the timeit
package because that package uses CPU time instead of system time.
That means that any waiting, like with threadDelay
would not be counted.
Note that this does not evaluate the result, on purpose.
Constructors
Timed | |
Fields
|
Instances
Functor Timed Source # | |
Eq a => Eq (Timed a) Source # | |
Show a => Show (Timed a) Source # | |
Generic (Timed a) Source # | |
type Rep (Timed a) Source # | |
Defined in Test.Syd.Run type Rep (Timed a) = D1 ('MetaData "Timed" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) (C1 ('MetaCons "Timed" 'PrefixI 'True) (S1 ('MetaSel ('Just "timedValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "timedTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) |