Copyright | (c) Sjoerd Visscher 2014 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell98 |
Class of data structures with 2 type arguments that can be unfolded.
Synopsis
- class Biunfoldable t where
- biunfold_ :: (Biunfoldable t, Unfolder f) => f (t () ())
- biunfoldBF :: (Biunfoldable t, Unfolder f) => f a -> f b -> f (t a b)
- biunfoldBF_ :: (Biunfoldable t, Unfolder f) => f (t () ())
- biunfoldr :: Biunfoldable t => (c -> Maybe (a, c)) -> (c -> Maybe (b, c)) -> c -> Maybe (t a b)
- fromLists :: Biunfoldable t => [a] -> [b] -> Maybe (t a b)
- randomDefault :: (Random a, Random b, RandomGen g, Biunfoldable t) => g -> (t a b, g)
- arbitraryDefault :: (Arbitrary a, Arbitrary b, Biunfoldable t) => Gen (t a b)
Biunfoldable
class Biunfoldable t where Source #
Data structures with 2 type arguments (kind * -> * -> *
) that can be unfolded.
For example, given a data type
data Tree a b = Empty | Leaf a | Node (Tree a b) b (Tree a b)
a suitable instance would be
instance Biunfoldable Tree where biunfold fa fb = choose [ pure Empty , Leaf <$> fa , Node <$> biunfold fa fb <*> fb <*> biunfold fa fb ]
i.e. it follows closely the instance for Bitraversable
, but instead of matching on an input value,
we choose
from a list of all cases.
biunfold :: Unfolder f => f a -> f b -> f (t a b) Source #
Given a way to generate elements, return a way to generate structures containing those elements.
Instances
Biunfoldable Either Source # | |
Biunfoldable (,) Source # | |
Defined in Data.Biunfoldable | |
Biunfoldable (Constant :: Type -> Type -> Type) Source # | |
biunfold_ :: (Biunfoldable t, Unfolder f) => f (t () ()) Source #
Unfold the structure, always using ()
as elements.
biunfoldBF :: (Biunfoldable t, Unfolder f) => f a -> f b -> f (t a b) Source #
Breadth-first unfold, which orders the result by the number of choose
calls.
biunfoldBF_ :: (Biunfoldable t, Unfolder f) => f (t () ()) Source #
Unfold the structure breadth-first, always using ()
as elements.
Specific unfolds
biunfoldr :: Biunfoldable t => (c -> Maybe (a, c)) -> (c -> Maybe (b, c)) -> c -> Maybe (t a b) Source #
biunfoldr
builds a data structure from a seed value.
fromLists :: Biunfoldable t => [a] -> [b] -> Maybe (t a b) Source #
Create a data structure using the lists 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 lists.
randomDefault :: (Random a, Random b, RandomGen g, Biunfoldable t) => g -> (t a b, g) Source #
Generate a random value, can be used as default instance for Random
.
arbitraryDefault :: (Arbitrary a, Arbitrary b, Biunfoldable t) => Gen (t a b) Source #
Provides a QuickCheck generator, can be used as default instance for Arbitrary
.