sydtest-0.1.0.0: A modern testing framework for Haskell with good defaults and advanced testing features.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Syd.Run

Description

This module defines the IsTest class and the different instances for it.

Synopsis

Documentation

class IsTest e where Source #

Associated Types

type Arg1 e Source #

type Arg2 e Source #

Methods

runTest :: e -> TestRunSettings -> ((Arg1 e -> Arg2 e -> IO ()) -> IO ()) -> IO TestRunResult Source #

Instances

Instances details
IsTest Bool Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 Bool Source #

type Arg2 Bool Source #

Methods

runTest :: Bool -> TestRunSettings -> ((Arg1 Bool -> Arg2 Bool -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest Property Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 Property Source #

type Arg2 Property Source #

IsTest (IO ()) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (IO ()) Source #

type Arg2 (IO ()) Source #

Methods

runTest :: IO () -> TestRunSettings -> ((Arg1 (IO ()) -> Arg2 (IO ()) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (IO (GoldenTest a)) Source #

type Arg2 (IO (GoldenTest a)) Source #

Methods

runTest :: IO (GoldenTest a) -> TestRunSettings -> ((Arg1 (IO (GoldenTest a)) -> Arg2 (IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (GoldenTest a) Source #

type Arg2 (GoldenTest a) Source #

Methods

runTest :: GoldenTest a -> TestRunSettings -> ((Arg1 (GoldenTest a) -> Arg2 (GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> GoldenTest a) Source #

type Arg2 (arg -> GoldenTest a) Source #

Methods

runTest :: (arg -> GoldenTest a) -> TestRunSettings -> ((Arg1 (arg -> GoldenTest a) -> Arg2 (arg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> Property) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> Property) Source #

type Arg2 (outerArgs -> innerArg -> Property) Source #

Methods

runTest :: (outerArgs -> innerArg -> Property) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> Property) -> Arg2 (outerArgs -> innerArg -> Property) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> Property) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> Property) Source #

type Arg2 (arg -> Property) Source #

Methods

runTest :: (arg -> Property) -> TestRunSettings -> ((Arg1 (arg -> Property) -> Arg2 (arg -> Property) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> IO ()) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> IO ()) Source #

type Arg2 (outerArgs -> innerArg -> IO ()) Source #

Methods

runTest :: (outerArgs -> innerArg -> IO ()) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> IO ()) -> Arg2 (outerArgs -> innerArg -> IO ()) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> IO ()) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> IO ()) Source #

type Arg2 (arg -> IO ()) Source #

Methods

runTest :: (arg -> IO ()) -> TestRunSettings -> ((Arg1 (arg -> IO ()) -> Arg2 (arg -> IO ()) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> Bool) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> Bool) Source #

type Arg2 (outerArgs -> innerArg -> Bool) Source #

Methods

runTest :: (outerArgs -> innerArg -> Bool) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> Bool) -> Arg2 (outerArgs -> innerArg -> Bool) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> Bool) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> Bool) Source #

type Arg2 (arg -> Bool) Source #

Methods

runTest :: (arg -> Bool) -> TestRunSettings -> ((Arg1 (arg -> Bool) -> Arg2 (arg -> Bool) -> IO ()) -> IO ()) -> IO TestRunResult 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 #

aroundProperty :: ((a -> b -> IO ()) -> IO ()) -> (a -> b -> Property) -> Property 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 

Instances

Instances details
IsTest (IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (IO (GoldenTest a)) Source #

type Arg2 (IO (GoldenTest a)) Source #

Methods

runTest :: IO (GoldenTest a) -> TestRunSettings -> ((Arg1 (IO (GoldenTest a)) -> Arg2 (IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (GoldenTest a) Source #

type Arg2 (GoldenTest a) Source #

Methods

runTest :: GoldenTest a -> TestRunSettings -> ((Arg1 (GoldenTest a) -> Arg2 (GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> GoldenTest a) Source #

type Arg2 (arg -> GoldenTest a) Source #

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 # 
Instance details

Defined in Test.Syd.Run

type Arg1 (IO (GoldenTest a)) = ()
type Arg1 (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (GoldenTest a) = ()
type Arg2 (IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (IO (GoldenTest a)) = ()
type Arg2 (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (GoldenTest a) = ()
type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) = outerArgs
type Arg1 (arg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (arg -> IO (GoldenTest a)) = ()
type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (outerArgs -> innerArg -> GoldenTest a) = outerArgs
type Arg1 (arg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (arg -> GoldenTest a) = ()
type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) = innerArg
type Arg2 (arg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (arg -> IO (GoldenTest a)) = arg
type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (outerArgs -> innerArg -> GoldenTest a) = innerArg
type Arg2 (arg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (arg -> GoldenTest a) = arg

runGoldenTestWithArg :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ((outerArgs -> innerArg -> IO ()) -> IO ()) -> IO TestRunResult Source #

type Test = IO () Source #

data TestRunSettings Source #

Instances

Instances details
Show TestRunSettings Source # 
Instance details

Defined in Test.Syd.Run

Generic TestRunSettings Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep TestRunSettings :: Type -> Type #

MonadReader TestRunSettings (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

ask :: TestDefM outers inner TestRunSettings #

local :: (TestRunSettings -> TestRunSettings) -> TestDefM outers inner a -> TestDefM outers inner a #

reader :: (TestRunSettings -> a) -> TestDefM outers inner a #

type Rep TestRunSettings Source # 
Instance details

Defined in Test.Syd.Run

type Rep TestRunSettings = D1 ('MetaData "TestRunSettings" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) (C1 ('MetaCons "TestRunSettings" 'PrefixI 'True) ((S1 ('MetaSel ('Just "testRunSettingSeed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "testRunSettingMaxSuccess") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "testRunSettingMaxSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "testRunSettingMaxDiscardRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "testRunSettingMaxShrinks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "testRunSettingGoldenStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "testRunSettingGoldenReset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

data TestRunResult Source #

Instances

Instances details
Eq TestRunResult Source # 
Instance details

Defined in Test.Syd.Run

Show TestRunResult Source # 
Instance details

Defined in Test.Syd.Run

Generic TestRunResult Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep TestRunResult :: Type -> Type #

type Rep TestRunResult Source # 
Instance details

Defined in Test.Syd.Run

type Rep TestRunResult = D1 ('MetaData "TestRunResult" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) (C1 ('MetaCons "TestRunResult" 'PrefixI 'True) (((S1 ('MetaSel ('Just "testRunResultStatus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestStatus) :*: S1 ('MetaSel ('Just "testRunResultException") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Either String Assertion)))) :*: (S1 ('MetaSel ('Just "testRunResultNumTests") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word)) :*: (S1 ('MetaSel ('Just "testRunResultNumShrinks") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word)) :*: S1 ('MetaSel ('Just "testRunResultFailingInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "testRunResultLabels") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Map [String] Int))) :*: S1 ('MetaSel ('Just "testRunResultClasses") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Map String Int)))) :*: (S1 ('MetaSel ('Just "testRunResultTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Map String (Map String Int)))) :*: (S1 ('MetaSel ('Just "testRunResultGoldenCase") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe GoldenCase)) :*: S1 ('MetaSel ('Just "testRunResultExtraInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe String)))))))

data TestStatus Source #

Constructors

TestPassed 
TestFailed 

Instances

Instances details
Eq TestStatus Source # 
Instance details

Defined in Test.Syd.Run

Show TestStatus Source # 
Instance details

Defined in Test.Syd.Run

Generic TestStatus Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep TestStatus :: Type -> Type #

type Rep TestStatus Source # 
Instance details

Defined in Test.Syd.Run

type Rep TestStatus = D1 ('MetaData "TestStatus" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) (C1 ('MetaCons "TestPassed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TestFailed" 'PrefixI 'False) (U1 :: Type -> Type))

data Assertion Source #

Instances

Instances details
Eq Assertion Source # 
Instance details

Defined in Test.Syd.Run

Show Assertion Source # 
Instance details

Defined in Test.Syd.Run

Generic Assertion Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep Assertion :: Type -> Type #

Exception Assertion Source # 
Instance details

Defined in Test.Syd.Run

type Rep Assertion Source # 
Instance details

Defined in Test.Syd.Run

type Rep Assertion = D1 ('MetaData "Assertion" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) ((C1 ('MetaCons "NotEqualButShouldHaveBeenEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "EqualButShouldNotHaveBeenEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PredicateSucceededButShouldHaveFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))) :+: (C1 ('MetaCons "PredicateFailedButShouldHaveSucceeded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :+: (C1 ('MetaCons "ExpectationFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Context" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Assertion) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

data GoldenCase Source #

Instances

Instances details
Eq GoldenCase Source # 
Instance details

Defined in Test.Syd.Run

Show GoldenCase Source # 
Instance details

Defined in Test.Syd.Run

Generic GoldenCase Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep GoldenCase :: Type -> Type #

type Rep GoldenCase Source # 
Instance details

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.

data Timed a Source #

Constructors

Timed 

Fields

Instances

Instances details
Functor Timed Source # 
Instance details

Defined in Test.Syd.Run

Methods

fmap :: (a -> b) -> Timed a -> Timed b #

(<$) :: a -> Timed b -> Timed a #

Eq a => Eq (Timed a) Source # 
Instance details

Defined in Test.Syd.Run

Methods

(==) :: Timed a -> Timed a -> Bool #

(/=) :: Timed a -> Timed a -> Bool #

Show a => Show (Timed a) Source # 
Instance details

Defined in Test.Syd.Run

Methods

showsPrec :: Int -> Timed a -> ShowS #

show :: Timed a -> String #

showList :: [Timed a] -> ShowS #

Generic (Timed a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep (Timed a) :: Type -> Type #

Methods

from :: Timed a -> Rep (Timed a) x #

to :: Rep (Timed a) x -> Timed a #

type Rep (Timed a) Source # 
Instance details

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)))