hedgehog-fn-0.6: Function generation for `hedgehog`

Safe HaskellNone
LanguageHaskell2010

Hedgehog.Function.Internal

Synopsis

Documentation

data a :-> c where infixr 5 Source #

Shrinkable, showable functions

Claessen, K. (2012, September). Shrinking and showing functions:(functional pearl). In ACM SIGPLAN Notices (Vol. 47, No. 12, pp. 73-80). ACM.

Constructors

Unit :: c -> () :-> c 
Nil :: a :-> c 
Pair :: (a :-> (b :-> c)) -> (a, b) :-> c 
Sum :: (a :-> c) -> (b :-> c) -> Either a b :-> c 
Map :: (a -> b) -> (b -> a) -> (b :-> c) -> a :-> c 
Instances
Functor ((:->) r) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

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

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

(Show a, Show b) => Show (a :-> b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

showsPrec :: Int -> (a :-> b) -> ShowS #

show :: (a :-> b) -> String #

showList :: [a :-> b] -> ShowS #

table :: (a :-> c) -> [(a, c)] Source #

Tabulate the function

class GArg a where Source #

Minimal complete definition

gbuild'

Methods

gbuild' :: (a x -> c) -> a x :-> c Source #

Instances
GArg (V1 :: * -> *) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gbuild' :: (V1 x -> c) -> V1 x :-> c Source #

GArg (U1 :: * -> *) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gbuild' :: (U1 x -> c) -> U1 x :-> c Source #

Arg b => GArg (K1 a b :: * -> *) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gbuild' :: (K1 a b x -> c) -> K1 a b x :-> c Source #

(GArg a, GArg b) => GArg (a :+: b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gbuild' :: ((a :+: b) x -> c) -> (a :+: b) x :-> c Source #

(GArg a, GArg b) => GArg (a :*: b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gbuild' :: ((a :*: b) x -> c) -> (a :*: b) x :-> c Source #

GArg c => GArg (M1 a b c) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gbuild' :: (M1 a b c x -> c0) -> M1 a b c x :-> c0 Source #

gbuild :: (Generic a, GArg (Rep a)) => (a -> c) -> a :-> c Source #

Reify a function whose domain has an instance of Generic

class Arg a where Source #

instance Arg A where allows functions which take As to be reified

Methods

build :: (a -> c) -> a :-> c Source #

build :: (Generic a, GArg (Rep a)) => (a -> c) -> a :-> c Source #

Instances
Arg Bool Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Bool -> c) -> Bool :-> c Source #

Arg Int Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Int -> c) -> Int :-> c Source #

Arg Int8 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Int8 -> c) -> Int8 :-> c Source #

Arg Int16 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Int16 -> c) -> Int16 :-> c Source #

Arg Int32 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Int32 -> c) -> Int32 :-> c Source #

Arg Int64 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Int64 -> c) -> Int64 :-> c Source #

Arg Integer Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Integer -> c) -> Integer :-> c Source #

Arg Ordering Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Ordering -> c) -> Ordering :-> c Source #

Arg () Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (() -> c) -> () :-> c Source #

Arg Void Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Void -> c) -> Void :-> c Source #

Arg a => Arg [a] Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: ([a] -> c) -> [a] :-> c Source #

Arg a => Arg (Maybe a) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Maybe a -> c) -> Maybe a :-> c Source #

(Arg a, Arg b) => Arg (Either a b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: (Either a b -> c) -> Either a b :-> c Source #

(Arg a, Arg b) => Arg (a, b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

build :: ((a, b) -> c) -> (a, b) :-> c Source #

variant :: Word64 -> GenT m b -> GenT m b Source #

variant' :: Word64 -> CoGenT m b -> CoGenT m b Source #

class GVary a where Source #

Minimal complete definition

gvary'

Methods

gvary' :: CoGenT m (a x) Source #

Instances
GVary (V1 :: * -> *) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gvary' :: CoGenT m (V1 x) Source #

GVary (U1 :: * -> *) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gvary' :: CoGenT m (U1 x) Source #

Vary b => GVary (K1 a b :: * -> *) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gvary' :: CoGenT m (K1 a b x) Source #

(GVary a, GVary b) => GVary (a :+: b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gvary' :: CoGenT m ((a :+: b) x) Source #

(GVary a, GVary b) => GVary (a :*: b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gvary' :: CoGenT m ((a :*: b) x) Source #

GVary c => GVary (M1 a b c) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

gvary' :: CoGenT m (M1 a b c x) Source #

gvary :: (Generic a, GVary (Rep a)) => CoGenT m a Source #

Build a co-generator for a type which has a Generic instance

class Vary a where Source #

Vary provides a canonical co-generator for a type.

While technically there are many possible co-generators for a given type, we don't get any benefit from caring.

Methods

vary :: CoGenT m a Source #

vary :: (Generic a, GVary (Rep a)) => CoGenT m a Source #

Instances
Vary Bool Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Bool Source #

Vary Int Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Int Source #

Vary Int8 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Int8 Source #

Vary Int16 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Int16 Source #

Vary Int32 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Int32 Source #

Vary Int64 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Int64 Source #

Vary Integer Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Integer Source #

Vary Ordering Source # 
Instance details

Defined in Hedgehog.Function.Internal

Vary Word8 Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Word8 Source #

Vary () Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m () Source #

Vary Void Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m Void Source #

Vary a => Vary [a] Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m [a] Source #

Vary a => Vary (Maybe a) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m (Maybe a) Source #

(Vary a, Vary b) => Vary (Either a b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m (Either a b) Source #

(Vary a, Vary b) => Vary (a, b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

vary :: CoGenT m (a, b) Source #

varyIntegral :: Integral a => CoGenT m a Source #

Build a co-generator for an Integral type

newtype CoGenT m a Source #

A CoGenT m a is used to perturb a GenT m b based on the value of the a. This way, the generated function will have a varying (but still deterministic) right hand side.

Co-generators can be built using Divisible and Decidable, but it is recommended to derive Generic and use the default instance of the Vary type class.

CoGenT m ~ Op (Endo (GenT m b))

Constructors

CoGenT 

Fields

Instances
Divisible (CoGenT m) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

divide :: (a -> (b, c)) -> CoGenT m b -> CoGenT m c -> CoGenT m a #

conquer :: CoGenT m a #

Decidable (CoGenT m) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

lose :: (a -> Void) -> CoGenT m a #

choose :: (a -> Either b c) -> CoGenT m b -> CoGenT m c -> CoGenT m a #

Contravariant (CoGenT m) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

contramap :: (a -> b) -> CoGenT m b -> CoGenT m a #

(>$) :: b -> CoGenT m b -> CoGenT m a #

apply' :: (a :-> b) -> a -> Maybe b Source #

Evaluate a possibly partial function

unsafeApply :: (a :-> b) -> a -> b Source #

Evaluate a total function. Unsafe.

data Fn a b Source #

The type of randomly-generated functions

Constructors

Fn b (a :-> Tree (MaybeT Identity) b) 
Instances
(Show a, Show b) => Show (Fn a b) Source # 
Instance details

Defined in Hedgehog.Function.Internal

Methods

showsPrec :: Int -> Fn a b -> ShowS #

show :: Fn a b -> String #

showList :: [Fn a b] -> ShowS #

unsafeFromTree :: Functor m => Tree (MaybeT m) a -> m a Source #

Extract the root value from a Tree. Unsafe.

shrinkFn :: (b -> [b]) -> (a :-> b) -> [a :-> b] Source #

Shrink the function

shrinkTree :: Monad m => Tree (MaybeT m) a -> m [Tree (MaybeT m) a] Source #

apply :: Fn a b -> a -> b Source #

Evaluate an Fn

fnWith :: Arg a => CoGen a -> Gen b -> Gen (Fn a b) Source #

Generate a function using the user-supplied co-generator

fn :: (Arg a, Vary a) => Gen b -> Gen (Fn a b) Source #

Generate a function

forAllFn :: (Show a, Show b, Monad m) => Gen (Fn a b) -> PropertyT m (a -> b) Source #

Run the function generator to retrieve a function

via :: Arg b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c Source #

Reify a function via an isomorphism.

If your function's domain has no instance of Generic then you can still reify it using an isomorphism to a better domain type. For example, the Arg instance for Integral uses an isomorphism from Integral a => a to (Bool, [Bool]), where the first element is the sign, and the second element is the bit-string.

Note: via f g will only be well-behaved if g . f = id and f . g = id

gvia :: GArg b => (a -> b x) -> (b x -> a) -> (a -> c) -> a :-> c Source #

buildIntegral :: (Arg a, Integral a) => (a -> c) -> a :-> c Source #

Reify a function on Integrals