yaya-hedgehog-0.3.0.2: Hedgehog testing support for the Yaya recursion scheme library.
Safe HaskellUnsafe
LanguageHaskell2010

Yaya.Hedgehog.Fold

Synopsis

Documentation

corecursiveIsUnsafe :: forall t a. (Corecursive (->) (t (Pair a)) (Pair a), Projectable (->) (t (Pair a)) (Pair a), Corecursive (->) (t ((,) a)) ((,) a), Projectable (->) (t ((,) a)) ((,) a), Eq a, Show a) => Proxy t -> a -> Property Source #

Show that using a Recursive structure corecursively can lead to non-termination.

embeddableOfHeight Source #

Arguments

:: (Steppable (->) t f, Functor f) 
=> Gen (f Void)

A generator for terminal cases (leaf nodes).

-> (Gen t -> Gen (f t))

A generator for arbitrary cases. If the provided value generates terminal cases, then the resulting tree may have a height less than the Size, otherwise it will be a perfect tree with a height of exactly the provided Size.

-> Size 
-> Gen t 

Creates a generator for any Steppable type whose pattern functor has terminal cases (e.g., not Identity or `((,) a)`). leaf can only generate terminal cases, and branch can generate any case.

This is similar to recursive in that it separates the non-recursive cases from the recursive ones, except

  • the types here also ensure that the non-recursive cases aren’t recursive,
  • different generator distributions may be used for rec & non-rec cases, and
  • the non-recursive cases aren’t included in recursive calls (see above for why).

If there’s no existing Gen (f Void) for your pattern functor, you can either create one manually, or pass discard to the usual Gen a -> Gen (f a) generator.

NB: Hedgehog’s Size is signed, so this can raise an exception if given a negative Size.

genAlgebra :: (Steppable (->) t f, Functor f) => Gen (f Void) -> (Gen t -> Gen (f t)) -> Algebra (->) Maybe (Gen t) Source #

Builds a generic tree generator of a certain height.

genCorecursive :: Corecursive (->) t f => (a -> f a) -> Gen a -> Gen t Source #

Creates a generator for potentially-infinite values.

law_anaRefl :: (Eq t, Show t, Steppable (->) t f, Corecursive (->) t f, MonadTest m) => t -> m () Source #

NB: Since this requires both a Corecursive and Eq instance on the same type, it _likely_ requires instances from yaya-unsafe.

law_cataCancel :: (Eq a, Show a, Steppable (->) t f, Recursive (->) t f, Functor f, MonadTest m) => Algebra (->) f a -> f t -> m () Source #

law_cataCompose :: forall t f u g m b. (Eq b, Show b, Recursive (->) t f, Steppable (->) u g, Recursive (->) u g, MonadTest m) => Proxy u -> Algebra (->) g b -> (forall a. f a -> g a) -> t -> m () Source #

law_cataRefl :: (Eq t, Show t, Steppable (->) t f, Recursive (->) t f, MonadTest m) => t -> m () Source #

recursiveIsUnsafe :: forall t a. (Corecursive (->) (t (Pair a)) (Pair a), Projectable (->) (t (Pair a)) (Pair a), Recursive (->) (t (Pair a)) (Pair a), Corecursive (->) (t ((,) a)) ((,) a), Recursive (->) (t ((,) a)) ((,) a), Eq a, Show a) => Proxy t -> a -> Property Source #

Show that using a Corecursive structure recursively can lead to non-termination.