| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Rose
Description
Rose Trees are trees with an unbounded number of branches per node. Each node contains a value and zero or more subtrees.
Synopsis
- data Rose a
- pattern Rose :: a -> [Rose a] -> Rose a
- singleton :: a -> Rose a
- coiter :: (a -> [a]) -> a -> Rose a
- coiterW :: Comonad w => (w a -> [w a]) -> w a -> Rose a
- unfold :: (b -> (a, [b])) -> b -> Rose a
- unfoldM :: Monad m => (b -> m (a, [b])) -> b -> m (Rose a)
- telescoped :: Functor f => [(Rose a -> f (Rose a)) -> [Rose a] -> f [Rose a]] -> (a -> f a) -> Rose a -> f (Rose a)
- telescoped_ :: Functor f => [(Rose a -> f (Rose a)) -> [Rose a] -> f [Rose a]] -> (Rose a -> f (Rose a)) -> Rose a -> f (Rose a)
- shoots :: Applicative f => (a -> f a) -> Rose a -> f (Rose a)
- leaves :: Applicative f => (a -> f a) -> Rose a -> f (Rose a)
Documentation
A Rose tree. This type can be produced and consumed using the
Rose pattern.
Instances
| Monad Rose Source # | |
| Functor Rose Source # | |
| Applicative Rose Source # | |
| Foldable Rose Source # | |
Defined in Rose Methods fold :: Monoid m => Rose m -> m # foldMap :: Monoid m => (a -> m) -> Rose a -> m # foldMap' :: Monoid m => (a -> m) -> Rose a -> m # foldr :: (a -> b -> b) -> b -> Rose a -> b # foldr' :: (a -> b -> b) -> b -> Rose a -> b # foldl :: (b -> a -> b) -> b -> Rose a -> b # foldl' :: (b -> a -> b) -> b -> Rose a -> b # foldr1 :: (a -> a -> a) -> Rose a -> a # foldl1 :: (a -> a -> a) -> Rose a -> a # elem :: Eq a => a -> Rose a -> Bool # maximum :: Ord a => Rose a -> a # | |
| Traversable Rose Source # | |
| Eq1 Rose Source # | |
| Ord1 Rose Source # | |
| Read1 Rose Source # | |
| Show1 Rose Source # | |
| MonadZip Rose Source # | |
| Comonad Rose Source # | |
| ComonadCofree [] Rose Source # | |
| Eq a => Eq (Rose a) Source # | |
| Ord a => Ord (Rose a) Source # | |
| Read a => Read (Rose a) Source # | |
| Show a => Show (Rose a) Source # | |
| Generic (Rose a) Source # | |
| Generic1 Rose Source # | |
| type Rep (Rose a) Source # | |
| type Rep1 Rose Source # | |
singleton :: a -> Rose a Source #
Generate a singleton rose tree. It has no leaves and one shoot.
>>>singleton @Int 3Rose 3 []
coiter :: (a -> [a]) -> a -> Rose a Source #
Use coiteration to generate a rose tree from a seed.
The coiteration terminates when the generating function returns an empty list:
>>>'coiter' (\i -> if i > 3 then [] else [i + 1]) 0Rose 0 [Rose 1 [Rose 2 [Rose 3 [Rose 4 []]]]]
An infinite, lazy generator for the fibonacci sequence:
>>>take 10 $ map fst $ 'Data.Foldable.toList' $ 'coiter' (\(a, b) -> [(b, a + b)]) (0, 1)
unfoldM :: Monad m => (b -> m (a, [b])) -> b -> m (Rose a) Source #
Unfold a rose tree from a seed, monadically.
telescoped :: Functor f => [(Rose a -> f (Rose a)) -> [Rose a] -> f [Rose a]] -> (a -> f a) -> Rose a -> f (Rose a) Source #
Construct an Lens into a rose tree given a list of lenses into the base functor.
When the input list is empty, this is equivalent to _extract.
When the input list is non-empty, this composes the input lenses
with _unwrap to walk through the rose tree before using
_extract to get the element at the final location.
For more on lenses see the lens package on hackage.
telescoped :: [Lens' [Rosea] (Rosea)] -> Lens' (Rosea) a
telescoped :: [Traversal' [Rosea] (Rosea)] -> Traversal' (Rosea) a
telescoped :: [Getter [Rosea] (Rosea)] -> Getter (Rosea) a
telescoped :: [Fold [Rosea] (Rosea)] -> Fold (Rosea) a
telescoped :: [Setter' [Rosea] (Rosea)] -> Setter' (Rosea) a
telescoped_ :: Functor f => [(Rose a -> f (Rose a)) -> [Rose a] -> f [Rose a]] -> (Rose a -> f (Rose a)) -> Rose a -> f (Rose a) Source #
Construct an Lens into a rose tree given a list of lenses into the base functor.
The only difference between this and telescoped is that telescoped focuses on a single value, but this focuses on the entire remaining subtree.
When the input list is empty, this is equivalent to id.
When the input list is non-empty, this composes the input lenses
with _unwrap to walk through the rose tree.
For more on lenses see the lens package on hackage.
telescoped :: [Lens' [Rosea] (Rosea)] -> Lens' (Rosea) (Rosea)
telescoped :: [Traversal' [Rosea] (Rosea)] -> Traversal' (Rosea) (Rosea)
telescoped :: [Getter [Rosea] (Rosea)] -> Getter (Rosea) (Rosea)
telescoped :: [Fold [Rosea] (Rosea)] -> Fold (Rosea) (Rosea)
telescoped :: [Setter' [Rosea] (Rosea)] -> Setter' (Rosea) (Rosea)
shoots :: Applicative f => (a -> f a) -> Rose a -> f (Rose a) Source #
A Traversal' that gives access to all non-leaf elements of a rose tree,
where non-leaf is defined as x from Rose x xs where null xs is False.
Because this doesn't give access to all values in the rose tree, it cannot be used to change types (use traverse for that).
leaves :: Applicative f => (a -> f a) -> Rose a -> f (Rose a) Source #
A Traversal' that gives access to all leaf elements of a rose tree, where
leaf is defined as x from Rose x xs where null xs is True.
Because this doesn't give access to all values in the rose tree, it cannot
be used to change types (use traverse for that).