unfoldable-0.5.0: Class of data structures that can be unfolded.

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com
Safe HaskellNone

Data.Unfolder

Contents

Description

Unfolders provide a way to unfold data structures. They are basically Alternative instances, but the choose method allows the unfolder to do something special for the recursive positions of the data structure.

Synopsis

Unfolder

class Alternative f => Unfolder f whereSource

Unfolders provide a way to unfold data structures. The methods have default implementations in terms of Alternative, but you can implement choose to act on recursive positions of the data structure, or simply to provide a faster implementation than asum.

Methods

choose :: [f x] -> f xSource

Choose one of the values from the list.

chooseInt :: Int -> f IntSource

Given a number n, return a number between '0' and 'n - 1'.

Instances

Unfolder []

Don't choose but return all items.

Unfolder Maybe

Always choose the first item.

Unfolder Arb

Limit the depth of the generated data structure by dividing the given size by the number of recursive positions.

MonadPlus m => Unfolder (WrappedMonad m)

Derived instance.

Unfolder f => Unfolder (Reverse f)

Derived instance.

Unfolder f => Unfolder (Backwards f)

Derived instance.

Unfolder f => Unfolder (Lift f)

Derived instance.

(Functor m, Monad m) => Unfolder (MaybeT m)

Derived instance.

Applicative f => Unfolder (ListT f)

Derived instance.

Applicative f => Unfolder (BFS f)

Choose between values of a given depth only.

Unfolder f => Unfolder (DualA f)

Reverse the list passed to choose.

(ArrowZero a, ArrowPlus a) => Unfolder (WrappedArrow a b)

Derived instance.

(Monoid w, Unfolder m) => Unfolder (WriterT w m)

Derived instance.

(MonadPlus m, Unfolder m) => Unfolder (StateT s m)

Derived instance.

Unfolder m => Unfolder (ReaderT r m)

Derived instance.

(Functor m, Monad m, Error e) => Unfolder (ErrorT e m)

Derived instance.

(Unfolder p, Applicative q) => Unfolder (Compose p q)

Derived instance.

(Unfolder p, Unfolder q) => Unfolder (Product p q)

Derived instance.

(Functor m, Monad m, RandomGen g) => Unfolder (Random g m)

Choose randomly.

(Monoid w, MonadPlus m, Unfolder m) => Unfolder (RWST r w s m)

Derived instance.

chooseMonadDefault :: (Monad m, Unfolder m) => [m x] -> m xSource

If an unfolder is monadic, choose can be implemented in terms of chooseInt.

boundedEnum :: forall f a. (Unfolder f, Bounded a, Enum a) => f aSource

If a datatype is bounded and enumerable, we can use chooseInt to generate a value.

Unfolder instances

newtype DualA f a Source

DualA flips the '(|)' operator.

Constructors

DualA 

Fields

getDualA :: f a
 

Instances

Functor f => Functor (DualA f) 
Applicative f => Applicative (DualA f) 
Alternative f => Alternative (DualA f) 
Unfolder f => Unfolder (DualA f)

Reverse the list passed to choose.

newtype Random g m a Source

Constructors

Random 

Fields

getRandom :: StateT g m a
 

Instances

Monad m => Monad (Random g m) 
Functor m => Functor (Random g m) 
(Functor m, Monad m, RandomGen g) => MonadPlus (Random g m) 
(Monad m, Functor m) => Applicative (Random g m) 
(Functor m, Monad m, RandomGen g) => Alternative (Random g m) 
(Functor m, Monad m, RandomGen g) => Unfolder (Random g m)

Choose randomly.

newtype BFS f x Source

Return a generator of values of a given depth. Returns Nothing if there are no values of that depth or deeper. The depth is the number of choose calls.

Constructors

BFS 

Fields

getBFS :: Int -> Maybe [f x]
 

Instances

Functor f => Functor (BFS f) 
Applicative f => Applicative (BFS f) 
Applicative f => Alternative (BFS f) 
Applicative f => Unfolder (BFS f)

Choose between values of a given depth only.

runBFS :: Unfolder f => BFS f x -> f xSource

packBFS :: f x -> BFS f xSource

data Arb a Source

A variant of Test.QuickCheck.Gen, with failure and a count of the number of recursive positions.

Constructors

Arb Int (StdGen -> Int -> Maybe a) 

Instances

Functor Arb 
Applicative Arb 
Alternative Arb 
Unfolder Arb

Limit the depth of the generated data structure by dividing the given size by the number of recursive positions.