tasty-quickcheck-laws-0.0.3: Pre-built tasty trees for checking lawful class properties using QuickCheck

Copyright2018 Automattic Inc.
LicenseBSD3
MaintainerNathan Bloomfield (nbloomf@gmail.com)
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Test.Tasty.QuickCheck.Laws.ReaderMonad

Contents

Description

 
Synopsis

Documentation

testReaderMonadLaws Source #

Arguments

:: (Monad m, Eq r, Eq a, Eq b, Show t, Show a, Show (m a), Arbitrary t, Arbitrary r, Arbitrary a, Arbitrary (m a), Arbitrary (m b), CoArbitrary r, CoArbitrary a, Typeable m, Typeable r, Typeable a) 
=> Proxy m

Type constructor under test

-> Proxy t

Equality context for m

-> Proxy r

Reader type

-> Proxy a

Value type

-> Proxy b

Value type

-> (forall u. Eq u => t -> m u -> m u -> Bool)

Equality test

-> m r
ask
-> (forall u. (r -> r) -> m u -> m u)
local
-> TestTree 

Constructs a TestTree checking that the reader monad laws hold for m with reader type r and value types a and b, using a given equality test for values of type forall u. m u. The equality context type t is for constructors m from which we can only extract a value within a context, such as reader-like constructors.

Reader Monad Laws

testReaderMonadLawLocalAsk Source #

Arguments

:: (Monad m, Eq r, Show t, Arbitrary t, Arbitrary r, CoArbitrary r) 
=> Proxy m

Type constructor under test

-> Proxy t

Equality context for m

-> Proxy r

Reader type

-> (forall u. Eq u => t -> m u -> m u -> Bool)

Equality test

-> m r
ask
-> (forall u. (r -> r) -> m u -> m u)
local
-> TestTree 
local u ask === fmap u ask

testReaderMonadLawLocalLocal Source #

Arguments

:: (Monad m, Eq a, Show t, Show (m a), Arbitrary t, Arbitrary r, Arbitrary (m a), CoArbitrary r) 
=> Proxy m

Type constructor under test

-> Proxy t

Equality context for m

-> Proxy r

Reader type

-> Proxy a

Value type

-> (forall u. Eq u => t -> m u -> m u -> Bool)

Equality test

-> (forall u. (r -> r) -> m u -> m u)
local
-> TestTree 
local u (local v x) === local (v . u) x

testReaderMonadLawLocalThenAsk Source #

Arguments

:: (Monad m, Eq r, Show t, Show (m a), Arbitrary t, Arbitrary r, Arbitrary (m a), CoArbitrary r) 
=> Proxy m

Type constructor under test

-> Proxy t

Equality context for m

-> Proxy r

Reader type

-> Proxy a

Value type

-> (forall u. Eq u => t -> m u -> m u -> Bool)

Equality test

-> m r
ask
-> (forall u. (r -> r) -> m u -> m u)
local
-> TestTree 
local u ask === fmap u ask

testReaderMonadLawLocalReturn Source #

Arguments

:: (Monad m, Eq a, Show t, Show a, Arbitrary t, Arbitrary r, Arbitrary a, CoArbitrary r) 
=> Proxy m

Type constructor under test

-> Proxy t

Equality context for m

-> Proxy r

Reader type

-> Proxy a

Value type

-> (forall u. Eq u => t -> m u -> m u -> Bool)

Equality test

-> (forall u. (r -> r) -> m u -> m u)
local
-> TestTree 
local u (return a) === return a

testReaderMonadLawLocalBind Source #

Arguments

:: (Monad m, Eq b, Show t, Show a, Show (m a), Arbitrary t, Arbitrary r, Arbitrary a, Arbitrary (m a), Arbitrary (m b), CoArbitrary r, CoArbitrary a) 
=> Proxy m

Type constructor under test

-> Proxy t

Equality context for m

-> Proxy r

Reader type

-> Proxy a

Value type

-> Proxy b

Value type

-> (forall u. Eq u => t -> m u -> m u -> Bool)

Equality test

-> (forall u. (r -> r) -> m u -> m u)

local

-> TestTree 
local u (x >>= f) === local u x >>= (local u . f)