unfoldable-1.0.1: Class of data structures that can be unfolded.
Copyright(c) Sjoerd Visscher 2014
LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Unfolder

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 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'.

Minimal complete definition

Nothing

Methods

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'.

Instances

Instances details
Unfolder [] Source #

Don't choose but return all items.

Instance details

Defined in Data.Unfolder

Methods

choose :: [[a]] -> [a] Source #

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

chooseInt :: Int -> [Int] Source #

Unfolder Maybe Source #

Always choose the first item.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Maybe a] -> Maybe a Source #

chooseMap :: (a -> Maybe b) -> [a] -> Maybe b Source #

chooseInt :: Int -> Maybe Int Source #

Unfolder Seq Source #

Don't choose but return all items.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Seq a] -> Seq a Source #

chooseMap :: (a -> Seq b) -> [a] -> Seq b Source #

chooseInt :: Int -> Seq Int Source #

Unfolder Nth Source #

Get the nth value from the sequence of all possible values.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Nth a] -> Nth a Source #

chooseMap :: (a -> Nth b) -> [a] -> Nth b Source #

chooseInt :: Int -> Nth Int Source #

Unfolder Arb Source #

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

Instance details

Defined in Data.Unfolder

Methods

choose :: [Arb a] -> Arb a Source #

chooseMap :: (a -> Arb b) -> [a] -> Arb b Source #

chooseInt :: Int -> Arb Int Source #

MonadPlus m => Unfolder (WrappedMonad m) Source #

Derived instance.

Instance details

Defined in Data.Unfolder

Unfolder f => Unfolder (Lift f) Source #

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Lift f a] -> Lift f a Source #

chooseMap :: (a -> Lift f b) -> [a] -> Lift f b Source #

chooseInt :: Int -> Lift f Int Source #

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

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [MaybeT m a] -> MaybeT m a Source #

chooseMap :: (a -> MaybeT m b) -> [a] -> MaybeT m b Source #

chooseInt :: Int -> MaybeT m Int Source #

Applicative f => Unfolder (ListT f) Source #

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [ListT f a] -> ListT f a Source #

chooseMap :: (a -> ListT f b) -> [a] -> ListT f b Source #

chooseInt :: Int -> ListT f Int Source #

Applicative f => Unfolder (BFS f) Source #

Choose between values of a given depth only.

Instance details

Defined in Data.Unfolder

Methods

choose :: [BFS f a] -> BFS f a Source #

chooseMap :: (a -> BFS f b) -> [a] -> BFS f b Source #

chooseInt :: Int -> BFS f Int Source #

Unfolder f => Unfolder (WithRec f) Source #

Applies a certain function depending on the depth at every recursive position.

Instance details

Defined in Data.Unfolder

Methods

choose :: [WithRec f a] -> WithRec f a Source #

chooseMap :: (a -> WithRec f b) -> [a] -> WithRec f b Source #

chooseInt :: Int -> WithRec f Int Source #

Unfolder f => Unfolder (DualA f) Source #

Reverse the list passed to choose.

Instance details

Defined in Data.Unfolder

Methods

choose :: [DualA f a] -> DualA f a Source #

chooseMap :: (a -> DualA f b) -> [a] -> DualA f b Source #

chooseInt :: Int -> DualA f Int Source #

Num a => Unfolder (NumConst a) Source #

Unfolds to a constant numeric value. Useful for counting shapes.

Instance details

Defined in Data.Unfolder

Methods

choose :: [NumConst a a0] -> NumConst a a0 Source #

chooseMap :: (a0 -> NumConst a b) -> [a0] -> NumConst a b Source #

chooseInt :: Int -> NumConst a Int Source #

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

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [WrappedArrow a b a0] -> WrappedArrow a b a0 Source #

chooseMap :: (a0 -> WrappedArrow a b b0) -> [a0] -> WrappedArrow a b b0 Source #

chooseInt :: Int -> WrappedArrow a b Int Source #

Unfolder f => Unfolder (Reverse f) Source #

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Reverse f a] -> Reverse f a Source #

chooseMap :: (a -> Reverse f b) -> [a] -> Reverse f b Source #

chooseInt :: Int -> Reverse f Int Source #

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

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [WriterT w m a] -> WriterT w m a Source #

chooseMap :: (a -> WriterT w m b) -> [a] -> WriterT w m b Source #

chooseInt :: Int -> WriterT w m Int Source #

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

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [StateT s m a] -> StateT s m a Source #

chooseMap :: (a -> StateT s m b) -> [a] -> StateT s m b Source #

chooseInt :: Int -> StateT s m Int Source #

Unfolder m => Unfolder (ReaderT r m) Source #

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [ReaderT r m a] -> ReaderT r m a Source #

chooseMap :: (a -> ReaderT r m b) -> [a] -> ReaderT r m b Source #

chooseInt :: Int -> ReaderT r m Int Source #

(Functor m, Monad m, Monoid e) => Unfolder (ExceptT e m) Source #

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [ExceptT e m a] -> ExceptT e m a Source #

chooseMap :: (a -> ExceptT e m b) -> [a] -> ExceptT e m b Source #

chooseInt :: Int -> ExceptT e m Int Source #

Unfolder f => Unfolder (Backwards f) Source #

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Backwards f a] -> Backwards f a Source #

chooseMap :: (a -> Backwards f b) -> [a] -> Backwards f b Source #

chooseInt :: Int -> Backwards f Int Source #

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

Choose randomly.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Random g m a] -> Random g m a Source #

chooseMap :: (a -> Random g m b) -> [a] -> Random g m b Source #

chooseInt :: Int -> Random g m Int Source #

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

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Product p q a] -> Product p q a Source #

chooseMap :: (a -> Product p q b) -> [a] -> Product p q b Source #

chooseInt :: Int -> Product p q Int Source #

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

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Compose p q a] -> Compose p q a Source #

chooseMap :: (a -> Compose p q b) -> [a] -> Compose p q b Source #

chooseInt :: Int -> Compose p q Int Source #

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

Derived instance.

Instance details

Defined in Data.Unfolder

Methods

choose :: [RWST r w s m a] -> RWST r w s m a Source #

chooseMap :: (a -> RWST r w s m b) -> [a] -> RWST r w s m b Source #

chooseInt :: Int -> RWST r w s m Int Source #

chooseMonadDefault :: (Monad m, Unfolder m) => [m a] -> m a Source #

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

chooseMapMonadDefault :: (Monad m, Unfolder m) => (a -> m b) -> [a] -> m b Source #

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

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 *).

betweenD :: (Unfolder f, Enum a) => a -> a -> f a Source #

betweenD uses choose to generate a value. It chooses between the lower bound and one of the higher values. This means that f.e. breadth-first unfolding and arbitrary will prefer lower values.

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

newtype Random g m a Source #

Constructors

Random 

Fields

Instances

Instances details
Monad m => Monad (Random g m) Source # 
Instance details

Defined in Data.Unfolder

Methods

(>>=) :: Random g m a -> (a -> Random g m b) -> Random g m b #

(>>) :: Random g m a -> Random g m b -> Random g m b #

return :: a -> Random g m a #

Functor m => Functor (Random g m) Source # 
Instance details

Defined in Data.Unfolder

Methods

fmap :: (a -> b) -> Random g m a -> Random g m b #

(<$) :: a -> Random g m b -> Random g m a #

Monad m => Applicative (Random g m) Source # 
Instance details

Defined in Data.Unfolder

Methods

pure :: a -> Random g m a #

(<*>) :: Random g m (a -> b) -> Random g m a -> Random g m b #

liftA2 :: (a -> b -> c) -> Random g m a -> Random g m b -> Random g m c #

(*>) :: Random g m a -> Random g m b -> Random g m b #

(<*) :: Random g m a -> Random g m b -> Random g m a #

(Functor m, Monad m, RandomGen g) => Alternative (Random g m) Source # 
Instance details

Defined in Data.Unfolder

Methods

empty :: Random g m a #

(<|>) :: Random g m a -> Random g m a -> Random g m a #

some :: Random g m a -> Random g m [a] #

many :: Random g m a -> Random g m [a] #

(Functor m, Monad m, RandomGen g) => MonadPlus (Random g m) Source # 
Instance details

Defined in Data.Unfolder

Methods

mzero :: Random g m a #

mplus :: Random g m a -> Random g m a -> Random g m a #

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

Choose randomly.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Random g m a] -> Random g m a Source #

chooseMap :: (a -> Random g m b) -> [a] -> Random g m b Source #

chooseInt :: Int -> Random g m Int Source #

data Arb a Source #

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

Constructors

Arb Int Int (Gen (Maybe a)) 

Instances

Instances details
Functor Arb Source # 
Instance details

Defined in Data.Unfolder

Methods

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

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

Applicative Arb Source # 
Instance details

Defined in Data.Unfolder

Methods

pure :: a -> Arb a #

(<*>) :: Arb (a -> b) -> Arb a -> Arb b #

liftA2 :: (a -> b -> c) -> Arb a -> Arb b -> Arb c #

(*>) :: Arb a -> Arb b -> Arb b #

(<*) :: Arb a -> Arb b -> Arb a #

Alternative Arb Source # 
Instance details

Defined in Data.Unfolder

Methods

empty :: Arb a #

(<|>) :: Arb a -> Arb a -> Arb a #

some :: Arb a -> Arb [a] #

many :: Arb a -> Arb [a] #

Unfolder Arb Source #

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

Instance details

Defined in Data.Unfolder

Methods

choose :: [Arb a] -> Arb a Source #

chooseMap :: (a -> Arb b) -> [a] -> Arb b Source #

chooseInt :: Int -> Arb Int Source #

newtype NumConst a x Source #

Variant of Constant that does multiplication of the constants for <*> and addition for <|>.

Constructors

NumConst 

Fields

Instances

Instances details
Functor (NumConst a) Source # 
Instance details

Defined in Data.Unfolder

Methods

fmap :: (a0 -> b) -> NumConst a a0 -> NumConst a b #

(<$) :: a0 -> NumConst a b -> NumConst a a0 #

Num a => Applicative (NumConst a) Source # 
Instance details

Defined in Data.Unfolder

Methods

pure :: a0 -> NumConst a a0 #

(<*>) :: NumConst a (a0 -> b) -> NumConst a a0 -> NumConst a b #

liftA2 :: (a0 -> b -> c) -> NumConst a a0 -> NumConst a b -> NumConst a c #

(*>) :: NumConst a a0 -> NumConst a b -> NumConst a b #

(<*) :: NumConst a a0 -> NumConst a b -> NumConst a a0 #

Num a => Alternative (NumConst a) Source # 
Instance details

Defined in Data.Unfolder

Methods

empty :: NumConst a a0 #

(<|>) :: NumConst a a0 -> NumConst a a0 -> NumConst a a0 #

some :: NumConst a a0 -> NumConst a [a0] #

many :: NumConst a a0 -> NumConst a [a0] #

Num a => Unfolder (NumConst a) Source #

Unfolds to a constant numeric value. Useful for counting shapes.

Instance details

Defined in Data.Unfolder

Methods

choose :: [NumConst a a0] -> NumConst a a0 Source #

chooseMap :: (a0 -> NumConst a b) -> [a0] -> NumConst a b Source #

chooseInt :: Int -> NumConst a Int Source #

Eq a => Eq (NumConst a x) Source # 
Instance details

Defined in Data.Unfolder

Methods

(==) :: NumConst a x -> NumConst a x -> Bool #

(/=) :: NumConst a x -> NumConst a x -> Bool #

Show a => Show (NumConst a x) Source # 
Instance details

Defined in Data.Unfolder

Methods

showsPrec :: Int -> NumConst a x -> ShowS #

show :: NumConst a x -> String #

showList :: [NumConst a x] -> ShowS #

data Nth a Source #

Constructors

Nth 

Fields

Instances

Instances details
Functor Nth Source # 
Instance details

Defined in Data.Unfolder

Methods

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

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

Applicative Nth Source # 
Instance details

Defined in Data.Unfolder

Methods

pure :: a -> Nth a #

(<*>) :: Nth (a -> b) -> Nth a -> Nth b #

liftA2 :: (a -> b -> c) -> Nth a -> Nth b -> Nth c #

(*>) :: Nth a -> Nth b -> Nth b #

(<*) :: Nth a -> Nth b -> Nth a #

Alternative Nth Source # 
Instance details

Defined in Data.Unfolder

Methods

empty :: Nth a #

(<|>) :: Nth a -> Nth a -> Nth a #

some :: Nth a -> Nth [a] #

many :: Nth a -> Nth [a] #

Unfolder Nth Source #

Get the nth value from the sequence of all possible values.

Instance details

Defined in Data.Unfolder

Methods

choose :: [Nth a] -> Nth a Source #

chooseMap :: (a -> Nth b) -> [a] -> Nth b Source #

chooseInt :: Int -> Nth Int Source #

UnfolderTransformer

class UnfolderTransformer t where Source #

An UnfolderTransformer changes the way an Unfolder unfolds.

Methods

lift :: Unfolder f => f a -> t f a Source #

Lift a computation from the argument unfolder to the constructed unfolder.

Instances

Instances details
UnfolderTransformer BFS Source # 
Instance details

Defined in Data.Unfolder

Methods

lift :: Unfolder f => f a -> BFS f a Source #

UnfolderTransformer WithRec Source # 
Instance details

Defined in Data.Unfolder

Methods

lift :: Unfolder f => f a -> WithRec f a Source #

UnfolderTransformer DualA Source # 
Instance details

Defined in Data.Unfolder

Methods

lift :: Unfolder f => f a -> DualA f a Source #

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

newtype DualA f a Source #

DualA flips the <|> operator from Alternative.

Constructors

DualA 

Fields

Instances

Instances details
UnfolderTransformer DualA Source # 
Instance details

Defined in Data.Unfolder

Methods

lift :: Unfolder f => f a -> DualA f a Source #

Functor f => Functor (DualA f) Source # 
Instance details

Defined in Data.Unfolder

Methods

fmap :: (a -> b) -> DualA f a -> DualA f b #

(<$) :: a -> DualA f b -> DualA f a #

Applicative f => Applicative (DualA f) Source # 
Instance details

Defined in Data.Unfolder

Methods

pure :: a -> DualA f a #

(<*>) :: DualA f (a -> b) -> DualA f a -> DualA f b #

liftA2 :: (a -> b -> c) -> DualA f a -> DualA f b -> DualA f c #

(*>) :: DualA f a -> DualA f b -> DualA f b #

(<*) :: DualA f a -> DualA f b -> DualA f a #

Alternative f => Alternative (DualA f) Source # 
Instance details

Defined in Data.Unfolder

Methods

empty :: DualA f a #

(<|>) :: DualA f a -> DualA f a -> DualA f a #

some :: DualA f a -> DualA f [a] #

many :: DualA f a -> DualA f [a] #

Unfolder f => Unfolder (DualA f) Source #

Reverse the list passed to choose.

Instance details

Defined in Data.Unfolder

Methods

choose :: [DualA f a] -> DualA f a Source #

chooseMap :: (a -> DualA f b) -> [a] -> DualA f b Source #

chooseInt :: Int -> DualA f Int Source #

Eq (f a) => Eq (DualA f a) Source # 
Instance details

Defined in Data.Unfolder

Methods

(==) :: DualA f a -> DualA f a -> Bool #

(/=) :: DualA f a -> DualA f a -> Bool #

Show (f a) => Show (DualA f a) Source # 
Instance details

Defined in Data.Unfolder

Methods

showsPrec :: Int -> DualA f a -> ShowS #

show :: DualA f a -> String #

showList :: [DualA f a] -> ShowS #

data NT f g Source #

Natural transformations

Constructors

NT 

Fields

  • getNT :: forall a. f a -> g a
     

newtype WithRec f a Source #

Constructors

WithRec 

Fields

Instances

Instances details
UnfolderTransformer WithRec Source # 
Instance details

Defined in Data.Unfolder

Methods

lift :: Unfolder f => f a -> WithRec f a Source #

Functor f => Functor (WithRec f) Source # 
Instance details

Defined in Data.Unfolder

Methods

fmap :: (a -> b) -> WithRec f a -> WithRec f b #

(<$) :: a -> WithRec f b -> WithRec f a #

Applicative f => Applicative (WithRec f) Source # 
Instance details

Defined in Data.Unfolder

Methods

pure :: a -> WithRec f a #

(<*>) :: WithRec f (a -> b) -> WithRec f a -> WithRec f b #

liftA2 :: (a -> b -> c) -> WithRec f a -> WithRec f b -> WithRec f c #

(*>) :: WithRec f a -> WithRec f b -> WithRec f b #

(<*) :: WithRec f a -> WithRec f b -> WithRec f a #

Alternative f => Alternative (WithRec f) Source # 
Instance details

Defined in Data.Unfolder

Methods

empty :: WithRec f a #

(<|>) :: WithRec f a -> WithRec f a -> WithRec f a #

some :: WithRec f a -> WithRec f [a] #

many :: WithRec f a -> WithRec f [a] #

Unfolder f => Unfolder (WithRec f) Source #

Applies a certain function depending on the depth at every recursive position.

Instance details

Defined in Data.Unfolder

Methods

choose :: [WithRec f a] -> WithRec f a Source #

chooseMap :: (a -> WithRec f b) -> [a] -> WithRec f b Source #

chooseInt :: Int -> WithRec f Int Source #

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.

limitDepth :: Unfolder f => Int -> WithRec f a -> f a Source #

Limit the depth of an unfolding.

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

Instances

Instances details
UnfolderTransformer BFS Source # 
Instance details

Defined in Data.Unfolder

Methods

lift :: Unfolder f => f a -> BFS f a Source #

Functor f => Functor (BFS f) Source # 
Instance details

Defined in Data.Unfolder

Methods

fmap :: (a -> b) -> BFS f a -> BFS f b #

(<$) :: a -> BFS f b -> BFS f a #

Applicative f => Applicative (BFS f) Source # 
Instance details

Defined in Data.Unfolder

Methods

pure :: a -> BFS f a #

(<*>) :: BFS f (a -> b) -> BFS f a -> BFS f b #

liftA2 :: (a -> b -> c) -> BFS f a -> BFS f b -> BFS f c #

(*>) :: BFS f a -> BFS f b -> BFS f b #

(<*) :: BFS f a -> BFS f b -> BFS f a #

Applicative f => Alternative (BFS f) Source # 
Instance details

Defined in Data.Unfolder

Methods

empty :: BFS f a #

(<|>) :: BFS f a -> BFS f a -> BFS f a #

some :: BFS f a -> BFS f [a] #

many :: BFS f a -> BFS f [a] #

Applicative f => Unfolder (BFS f) Source #

Choose between values of a given depth only.

Instance details

Defined in Data.Unfolder

Methods

choose :: [BFS f a] -> BFS f a Source #

chooseMap :: (a -> BFS f b) -> [a] -> BFS f b Source #

chooseInt :: Int -> BFS f Int Source #

type Split = Int -> [(Int, Int)] Source #

bfs :: Unfolder f => BFS f x -> f x Source #

Change the order of unfolding to be breadth-first, by maximum depth of the components.

bfsBySum :: Unfolder f => BFS f x -> f x Source #

Change the order of unfolding to be breadth-first, by the sum of depths of the components.