Copyright | (c) Sjoerd Visscher 2014 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
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 a] -> m a
- chooseMapMonadDefault :: (Monad m, Unfolder m) => (a -> m b) -> [a] -> m b
- between :: (Unfolder f, Enum a) => a -> a -> f a
- betweenD :: (Unfolder f, Enum a) => a -> a -> f a
- boundedEnum :: (Unfolder f, Bounded a, Enum a) => f a
- boundedEnumD :: (Unfolder f, Bounded a, Enum a) => f a
- newtype Random g m a = Random {}
- data Arb a = Arb Int (Gen (Maybe a))
- arbUnit :: Arbitrary a => Arb a
- newtype NumConst a x = NumConst {
- getNumConst :: a
- data Nth a = Nth {}
- class UnfolderTransformer t where
- ala :: (UnfolderTransformer t, Unfolder f) => (t f b -> f b) -> (t f a -> t f b) -> f a -> f b
- ala2 :: (UnfolderTransformer t, Unfolder f) => (t f c -> f c) -> (t f a -> t f b -> t f c) -> f a -> f b -> f c
- ala3 :: (UnfolderTransformer t, Unfolder f) => (t f d -> f d) -> (t f a -> t f b -> t f c -> t f d) -> f a -> f b -> f c -> f d
- newtype DualA f a = DualA {
- getDualA :: f a
- data NT f g = NT {
- getNT :: forall a. f a -> g a
- newtype WithRec f a = WithRec {
- getWithRec :: ReaderT (Int -> NT f f) f a
- withRec :: (Int -> NT f f) -> WithRec f a -> f a
- limitDepth :: Unfolder f => Int -> WithRec f a -> f a
- newtype BFS f x = BFS {}
- type Split = Int -> [(Int, Int)]
- bfs :: Unfolder f => BFS f x -> f x
- bfsBySum :: Unfolder f => BFS f x -> f x
Unfolder
class Alternative f => Unfolder f where Source #
Unfolders provide a way to unfold data structures.
The methods have default implementations in terms of Alternative
,
but you can implement chooseMap
to act on recursive positions of the
data structure, or simply to provide a faster implementation than
'foldr ((|) . f) empty'.
choose :: [f a] -> f a Source #
Choose one of the values from the list.
chooseMap :: (a -> f b) -> [a] -> f b Source #
Choose one of the values from the list and apply the given function.
chooseInt :: Int -> f Int Source #
Given a number n
, return a number between '0' and 'n - 1'.
Unfolder [] Source # | Don't choose but return all items. |
Unfolder Maybe Source # | Always choose the first item. |
Unfolder Seq Source # | Don't choose but return all items. |
Unfolder Arb Source # | Limit the depth of the generated data structure by dividing the given size by the number of recursive positions. |
Unfolder Nth Source # | |
MonadPlus m => Unfolder (WrappedMonad m) Source # | Derived instance. |
Unfolder f => Unfolder (Lift f) Source # | Derived instance. |
(Functor m, Monad m) => Unfolder (MaybeT m) Source # | Derived instance. |
Applicative f => Unfolder (ListT f) Source # | Derived instance. |
Num a => Unfolder (NumConst a) Source # | Unfolds to a constant numeric value. Useful for counting shapes. |
Applicative f => Unfolder (BFS f) Source # | Choose between values of a given depth only. |
Unfolder f => Unfolder (WithRec f) Source # | Applies a certain function depending on the depth at every recursive position. |
Unfolder f => Unfolder (DualA f) Source # | Reverse the list passed to choose. |
(ArrowZero a, ArrowPlus a) => Unfolder (WrappedArrow a b) Source # | Derived instance. |
Unfolder f => Unfolder (Reverse * f) Source # | Derived instance. |
(Monoid w, Unfolder m) => Unfolder (WriterT w m) Source # | Derived instance. |
(MonadPlus m, Unfolder m) => Unfolder (StateT s m) Source # | Derived instance. |
(Functor m, Monad m, Monoid e) => Unfolder (ExceptT e m) Source # | Derived instance. |
Unfolder f => Unfolder (Backwards * f) Source # | Derived instance. |
(Functor m, Monad m, RandomGen g) => Unfolder (Random g m) Source # | Choose randomly. |
(Unfolder p, Unfolder q) => Unfolder (Product * p q) Source # | Derived instance. |
Unfolder m => Unfolder (ReaderT * r m) Source # | Derived instance. |
(Unfolder p, Applicative q) => Unfolder (Compose * * p q) Source # | Derived instance. |
(Monoid w, MonadPlus m, Unfolder m) => Unfolder (RWST r w s m) Source # | Derived instance. |
chooseMonadDefault :: (Monad m, Unfolder m) => [m a] -> m a Source #
chooseMapMonadDefault :: (Monad m, Unfolder m) => (a -> m b) -> [a] -> m b Source #
between :: (Unfolder f, Enum a) => a -> a -> f a Source #
If a datatype is enumerable, we can use chooseInt
to generate a value.
This is the function to use if you want to unfold a datatype that has no type arguments (has kind *
).
boundedEnum :: (Unfolder f, Bounded a, Enum a) => f a Source #
If a datatype is also bounded, we can choose between all possible values.
boundedEnum = between minBound maxBound
boundedEnumD :: (Unfolder f, Bounded a, Enum a) => f a Source #
boundedEnumD = betweenD minBound maxBound
Unfolder instances
Monad m => Monad (Random g m) Source # | |
Functor m => Functor (Random g m) Source # | |
Monad m => Applicative (Random g m) Source # | |
(Functor m, Monad m, RandomGen g) => Alternative (Random g m) Source # | |
(Functor m, Monad m, RandomGen g) => MonadPlus (Random g m) Source # | |
(Functor m, Monad m, RandomGen g) => Unfolder (Random g m) Source # | Choose randomly. |
A variant of Test.QuickCheck.Gen, with failure and a count of the number of recursive positions.
Variant of Constant
that does multiplication of the constants for <*>
and addition for <|>
.
NumConst | |
|
UnfolderTransformer
class UnfolderTransformer t where Source #
An UnfolderTransformer
changes the way an Unfolder
unfolds.
ala :: (UnfolderTransformer t, Unfolder f) => (t f b -> f b) -> (t f a -> t f b) -> f a -> f b Source #
Run an unfolding function with one argument using an UnfolderTransformer
, given a way to run the transformer.
ala2 :: (UnfolderTransformer t, Unfolder f) => (t f c -> f c) -> (t f a -> t f b -> t f c) -> f a -> f b -> f c Source #
Run an unfolding function with two arguments using an UnfolderTransformer
, given a way to run the transformer.
ala3 :: (UnfolderTransformer t, Unfolder f) => (t f d -> f d) -> (t f a -> t f b -> t f c -> t f d) -> f a -> f b -> f c -> f d Source #
Run an unfolding function with three arguments using an UnfolderTransformer
, given a way to run the transformer.
UnfolderTransformer instances
DualA
flips the <|>
operator from Alternative
.
UnfolderTransformer DualA Source # | |
Functor f => Functor (DualA f) Source # | |
Applicative f => Applicative (DualA f) Source # | |
Alternative f => Alternative (DualA f) Source # | |
Unfolder f => Unfolder (DualA f) Source # | Reverse the list passed to choose. |
Eq (f a) => Eq (DualA f a) Source # | |
Show (f a) => Show (DualA f a) Source # | |
WithRec | |
|
UnfolderTransformer WithRec Source # | |
Functor f => Functor (WithRec f) Source # | |
Applicative f => Applicative (WithRec f) Source # | |
Alternative f => Alternative (WithRec f) Source # | |
Unfolder f => Unfolder (WithRec f) Source # | Applies a certain function depending on the depth at every recursive position. |
withRec :: (Int -> NT f f) -> WithRec f a -> f a Source #
Apply a certain function of type f a -> f a
to the result of a choose
.
The depth is passed as Int
, so you can apply a different function at each depth.
Because of a forall
, the function needs to be wrapped in a NT
constructor.
See limitDepth
for an example how to use this function.
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.
UnfolderTransformer BFS Source # | |
Functor f => Functor (BFS f) Source # | |
Applicative f => Applicative (BFS f) Source # | |
Applicative f => Alternative (BFS f) Source # | |
Applicative f => Unfolder (BFS f) Source # | Choose between values of a given depth only. |