| Safe Haskell | Safe-Infered |
|---|
Data.Unfoldable
Contents
- class Applicative f => Unfolder f where
- class Unfoldable t where
- unfold_ :: (Unfoldable t, Unfolder f) => f (t ())
- unfoldBF :: (Unfoldable t, Unfolder f, Alternative f) => f a -> f (t a)
- unfoldBF_ :: (Unfoldable t, Unfolder f, Alternative f) => f (t ())
- leftMost :: Unfoldable t => t ()
- rightMost :: Unfoldable t => t ()
- allDepthFirst :: Unfoldable t => [t ()]
- allBreadthFirst :: Unfoldable t => [t ()]
- randomDefault :: (Random a, RandomGen g, Unfoldable t) => g -> (t a, g)
- fromList :: Unfoldable t => [a] -> Maybe (t a)
Documentation
class Applicative f => Unfolder f whereSource
Unfolders provide a way to unfold data structures. The minimal implementation is choose.
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 Right | Always choose the last item. |
| Unfolder Left | Always choose the first item. |
| Unfolder m => Unfolder (Reverse m) | |
| (Alternative f, Unfolder f) => Unfolder (BFS f) | Choose between values of a given depth only. |
| (Monad m, Unfolder m) => Unfolder (StateT s m) | |
| Unfolder m => Unfolder (ReaderT r m) | |
| Unfolder m => Unfolder (ContT r m) | |
| (Unfolder p, Applicative q) => Unfolder (Compose p q) | |
| (Unfolder p, Unfolder q) => Unfolder (Product p q) | |
| (Functor m, Monad m, RandomGen g) => Unfolder (Random g m) | Choose randomly. |
class Unfoldable t whereSource
Data structures that can be unfolded.
For example, given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Unfoldable Tree where
unfold fa = choose
[ pure Empty
, Leaf <$> fa
, Node <$> unfold fa <*> fa <*> unfold fa
]
i.e. it follows closely the instance for Traversable, but instead of matching on an input value,
we choose from a list of all cases.
Methods
unfold :: Unfolder f => f a -> f (t a)Source
Given a way to generate elements, return a way to generate structures containing those elements.
Instances
| Unfoldable [] | |
| Unfoldable Maybe | |
| Unfoldable Identity | |
| (Bounded a, Enum a) => Unfoldable (Either a) | |
| (Bounded a, Enum a) => Unfoldable ((,) a) | |
| Unfoldable f => Unfoldable (Reverse f) | |
| (Bounded a, Enum a) => Unfoldable (Constant a) | |
| (Unfoldable p, Unfoldable q) => Unfoldable (Compose p q) | |
| (Unfoldable p, Unfoldable q) => Unfoldable (Product p q) |
unfold_ :: (Unfoldable t, Unfolder f) => f (t ())Source
Unfold the structure, always using '()' as elements.
unfoldBF :: (Unfoldable t, Unfolder f, Alternative f) => f a -> f (t a)Source
Breadth-first unfold
unfoldBF_ :: (Unfoldable t, Unfolder f, Alternative f) => f (t ())Source
Unfold the structure breadth-first, always using '()' as elements.
Specific unfolds
leftMost :: Unfoldable t => t ()Source
Always choose the first constructor.
rightMost :: Unfoldable t => t ()Source
Always choose the last constructor.
allDepthFirst :: Unfoldable t => [t ()]Source
Generate all the values depth first.
allBreadthFirst :: Unfoldable t => [t ()]Source
Generate all the values breadth first.
randomDefault :: (Random a, RandomGen g, Unfoldable t) => g -> (t a, g)Source
Generate a random value, can be used as default instance for Random.
fromList :: Unfoldable t => [a] -> Maybe (t a)Source
Create a data structure using the list as input. This can fail because there might not be a data structure with the same number of element positions as the number of elements in the list.