Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Testable representation of (higher-order) functions.
See the README for an introduction.
Synopsis
- data a :-> r
- applyFun :: (a :-> r) -> a -> r
- applyFun2 :: (a :-> (b :-> r)) -> a -> b -> r
- applyFun3 :: (a :-> (b :-> (c :-> r))) -> a -> b -> c -> r
- shrinkFun :: forall a r. (r -> [r]) -> (a :-> r) -> [a :-> r]
- showsPrecFun :: forall a r. ShowsPrec r -> ShowsPrec (a :-> r)
- indent :: String -> String
- type ShowsPrec r = Int -> r -> String -> String
- type Co gen a r = gen r -> gen (a :-> r)
- cogenEmbed :: Functor gen => FunName -> (a -> b) -> Co gen b r -> Co gen a r
- cogenIntegral :: (Applicative gen, Integral a) => TypeName -> Co gen a r
- cogenIntegral' :: Applicative gen => TypeName -> (a -> Integer) -> Co gen a r
- cogenFun :: Monad gen => Concrete a0 -> gen (Maybe a0) -> (a0 -> a) -> Co gen b ((a -> b) :-> r) -> Co gen (a -> b) r
- data Concrete r = Concrete {
- shrinkC :: r -> [r]
- showsPrecC :: ShowsPrec r
- type FunName = String
- type TypeName = String
- cogenGeneric :: forall a r gen. (Generic a, GCoGen a, Applicative gen) => GSumCo gen a r -> Co gen a r
- data a :+ b = a :+ b
- cogenList :: forall a r gen. Applicative gen => Co gen a ([a] :-> r) -> Co gen [a] r
- cogenConst :: Functor gen => Co gen a r
- cogenApply :: Functor gen => Concrete a0 -> (a0 -> a) -> a0 -> gen (b :-> ((a -> b) :-> r)) -> gen ((a -> b) :-> r)
- class Applicative gen => CoArbitrary gen a where
- coarbitrary :: forall r. Co gen a r
- coarbitraryGeneric :: forall a r gen. (Generic a, GCoArbitrary gen a) => Co gen a r
- class (Typeable_ a, GNormalize (Rep a), GenBranches (Rep a)) => GCoGen a
- class (GCoGen a, Applicative gen, GSumCoArb gen (Rep a)) => GCoArbitrary gen a
- type GSumCo gen a r = GSumCo_ gen (Rep a) r ()
Testable functions
data a :-> r infixr 1 Source #
Testable representation of functions (a -> r)
.
This representation supports random generation, shrinking, and printing, for property testing with QuickCheck or Hedgehog.
Higher-order functions can be represented.
Instances
Functor ((:->) a) Source # | |
Foldable ((:->) a) Source # | |
Defined in Test.Fun.Internal.Types fold :: Monoid m => (a :-> m) -> m # foldMap :: Monoid m => (a0 -> m) -> (a :-> a0) -> m # foldr :: (a0 -> b -> b) -> b -> (a :-> a0) -> b # foldr' :: (a0 -> b -> b) -> b -> (a :-> a0) -> b # foldl :: (b -> a0 -> b) -> b -> (a :-> a0) -> b # foldl' :: (b -> a0 -> b) -> b -> (a :-> a0) -> b # foldr1 :: (a0 -> a0 -> a0) -> (a :-> a0) -> a0 # foldl1 :: (a0 -> a0 -> a0) -> (a :-> a0) -> a0 # toList :: (a :-> a0) -> [a0] # elem :: Eq a0 => a0 -> (a :-> a0) -> Bool # maximum :: Ord a0 => (a :-> a0) -> a0 # minimum :: Ord a0 => (a :-> a0) -> a0 # | |
Traversable ((:->) a) Source # | |
Show r => Show (a :-> r) Source # | Pretty-printed |
applyFun3 :: (a :-> (b :-> (c :-> r))) -> a -> b -> c -> r Source #
Apply a ternary function representation.
Shrink and show
showsPrecFun :: forall a r. ShowsPrec r -> ShowsPrec (a :-> r) Source #
Prettify function representation.
indent :: String -> String Source #
Break up lines after braces and indent.
Example
Input:
\x -> case x :: Either _ _ of { Left x1 -> case x1 of { Left x2 -> () ; Right x2 -> case x2 of {} } ; Right x1 -> () }
Output:
\x -> case x :: Either _ _ of { Left x1 -> case x1 of { Left x2 -> () ; Right x2 -> case x2 of {} } ; Right x1 -> () }
Cogenerators
type Co gen a r = gen r -> gen (a :-> r) Source #
A "cogenerator" of a
is a random generator of functions with domain a
.
They are parameterized by a generator in the codomain r
.
More generally, we can make cogenerators to generate functions of arbitrary arities;
is only the type of unary cogenerators.Co
gen a r
gen r -> gen (a :-> r) -- Co gen a r gen r -> gen (a :-> b :-> r) gen r -> gen (a :-> b :-> c :-> r) gen r -> gen (a :-> b :-> c :-> d :-> r) -- etc.
More details
Cogenerators can be composed using id
and (
(the usual combinators
for functions).
The arity of a cogenerator .
)f
is the sum of the arities of .
gf
and g
.
id :: forall r. gen r -> gen r -- 0-ary cogenerator -- (1-ary) . (1-ary) = (2-ary) (.) :: (forall r. gen r -> gen (a :-> r)) -> (forall r. gen r -> gen (b :-> r)) -> (forall r. gen r -> gen (a :-> b :-> r)) -- (2-ary) . (1-ary) = (3-ary) (.) :: (forall r. gen r -> gen (a :-> b :-> r)) -> (forall r. gen r -> gen (c :-> r)) -> (forall r. gen r -> gen (a :-> b :-> c :-> r))
Note: the last type parameter r
should really be universally quantified
(as in the above pseudo type signatures), but instead we use more specialized
types to avoid making types higher-ranked.
Main combinators
cogenEmbed :: Functor gen => FunName -> (a -> b) -> Co gen b r -> Co gen a r Source #
Cogenerator for a type a
from a cogenerator for b
,
given an embedding function (a -> b)
,
and a name for that function (used for pretty-printing).
Example
The common usage is to construct cogenerators for newtypes.
-- Given some cogenerator of Fruit cogenFruit ::Co
Gen Fruit r -- Wrap Fruit in a newtype newtype Apple = Apple { unApple :: Fruit } cogenApple ::Co
Gen Apple r cogenApple =cogenEmbed
"unApple" cogenFruit
If cogenFruit
generates a function that looks like:
\y -> case y :: Fruit of { ... }
then cogenApple
will look like this,
where y
is replaced with unApple x
:
\x -> case unApple x :: Fruit of { ... }
cogenIntegral :: (Applicative gen, Integral a) => TypeName -> Co gen a r Source #
Cogenerator for an integral type. The name of the type is used for pretty-printing.
Example
cogenInteger ::Co
GenInteger
r cogenInteger =cogenIntegral
"Integer" cogenInt ::Co
GenInt
r cogenInt =cogenIntegral
"Int" cogenWord ::Co
GenWord
r cogenWord =cogenIntegral
"Word"
cogenIntegral' :: Applicative gen => TypeName -> (a -> Integer) -> Co gen a r Source #
Variant of cogenIntegral
with an explicit conversion to Integer
.
:: Monad gen | |
=> Concrete a0 | Shrink and show |
-> gen (Maybe a0) | Generate representations of argument values. |
-> (a0 -> a) | Interpret a representation |
-> Co gen b ((a -> b) :-> r) | Cogenerator of |
-> Co gen (a -> b) r |
Construct a cogenerator of functions (a -> b)
from a cogenerator of b
,
using gen (Maybe a0)
to generate random arguments until it returns
Nothing
.
Dictionary with shrinker and printer.
Used as part of the representation of higher-order functions with (
.:->
)
Concrete | |
|
Generic cogenerators
cogenGeneric :: forall a r gen. (Generic a, GCoGen a, Applicative gen) => GSumCo gen a r -> Co gen a r Source #
Cogenerator for generic types, parameterized by a list of cogenerators, one for each constructor.
The list is constructed with (
(pairs) and :+
)()
.
Example
-- Cogenerator for lists, parameterized by a cogenerator for elements.cogenList
:: forall a. (forall r.Co
Gen a r) -> (forall r.Co
Gen [a] r)cogenList
coa =cogenGeneric
gs where -- gs :: GSumCo Gen [a] r -- unfolds to -- gs :: (gen r -> gen r):+
-- Cogenerator for the empty list (gen r -> gen (a:->
[a]:->
r)):+
-- Cogenerator for non-empty lists () gs = id:+
(coa.
cogenList
coa):+
()
Heterogeneous products as nested pairs. These products must be terminated by ().
a :+ b :+ c :+ () -- the product of a, b, c
a :+ b infixr 2 |
Secondary combinators
cogenConst :: Functor gen => Co gen a r Source #
The trivial cogenerator which generates a constant function.
:: Functor gen | |
=> Concrete a0 | Shrink and show |
-> (a0 -> a) | Reify to value |
-> a0 | Value to inspect. |
-> gen (b :-> ((a -> b) :-> r)) | Cogenerator of |
-> gen ((a -> b) :-> r) |
Extend a cogenerator of functions (a -> b)
(i.e., a generator of higher-order
functions ((a -> b) -> r)
), applying the function to a given value a
and inspecting the result with a cogenerator of b
.
This is parameterized by a way to generate, shrink, and show values of
type a
or, more generally, some representation a0
of values of type a
.
Example
-- Assume Chips is some concrete type. concreteChips ::Concrete
Chips -- Assume we have a cogenerator of Fish. cogenFish :: forall r. Gen r -> Gen (Fish:->
r) -- Then we can use cogenApply to construct this function -- to transform cogenerators of functions (Chips -> Fish). cogenX :: forall r. Chips -> Gen ((Chips -> Fish):->
r) -> Gen ((Chips -> Fish):->
r) cogenX =cogenApply
concreteChipsid
.
cogenFish -- If we have some inputs... chips1, chips2, chips3 :: Chips -- ... we can construct a cogenerator of functions by iterating cogenX. cogenF :: forall r. Gen r -> Gen ((Chips -> Fish):->
r) cogenF = cogenX chips1.
cogenX chips2.
cogenX chips3.
cogenConst
CoArbitrary
class Applicative gen => CoArbitrary gen a where Source #
Implicit, default cogenerator.
coarbitrary :: forall r. Co gen a r Source #
Instances
coarbitraryGeneric :: forall a r gen. (Generic a, GCoArbitrary gen a) => Co gen a r Source #
Generic implementation of coarbitrary
.
-- Assuming MyData is a data type whose fields are all instances of CoArbitrary. instance CoArbitrary MyData where coarbitrary = coarbitraryGeneric
Generic classes
class (Typeable_ a, GNormalize (Rep a), GenBranches (Rep a)) => GCoGen a Source #
Class of types with generic cogenerators.
Instances
(Typeable_ a, GNormalize (Rep a), GenBranches (Rep a)) => GCoGen a Source # | |
Defined in Test.Fun.Internal.Generic |
class (GCoGen a, Applicative gen, GSumCoArb gen (Rep a)) => GCoArbitrary gen a Source #
Constraint for coarbitraryGeneric
.
Instances
(GCoGen a, Applicative gen, GSumCoArb gen (Rep a)) => GCoArbitrary gen a Source # | |
Defined in Test.Fun.Internal.Generic |