| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | sjoerd@w3future.com |
| Safe Haskell | None |
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.
- class Alternative f => Unfolder f where
- chooseMonadDefault :: (Monad m, Unfolder m) => [m x] -> m x
- boundedEnum :: forall f a. (Unfolder f, Bounded a, Enum a) => f a
- newtype DualA f a = DualA {
- getDualA :: f a
- newtype Random g m a = Random {}
- newtype BFS f x = BFS {}
- runBFS :: Unfolder f => BFS f x -> f x
- packBFS :: f x -> BFS f x
- data Arb a = Arb Int (StdGen -> Int -> Maybe a)
- arbUnit :: Arbitrary a => Arb a
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 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
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
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. |
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. |
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.
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. |
A variant of Test.QuickCheck.Gen, with failure and a count of the number of recursive positions.
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. |