| Copyright | (c) Sjoerd Visscher 2009 | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | sjoerd@w3future.com | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Data.FMList
Description
FoldMap lists: lists represented by their foldMap function.
Examples:
-- A right-infinite list c = 1 `cons` c
-- A left-infinite list d = d `snoc` 2
-- A middle-infinite list ?? e = c `append` d
*> head e 1 *> last e 2
- newtype FMList a = FM {}
 - transform :: (forall m. Monoid m => (a -> m) -> b -> m) -> FMList b -> FMList a
 - empty :: Alternative f => forall a. f a
 - singleton :: a -> FMList a
 - cons :: a -> FMList a -> FMList a
 - snoc :: FMList a -> a -> FMList a
 - pair :: a -> a -> FMList a
 - append :: FMList a -> FMList a -> FMList a
 - fromList :: [a] -> FMList a
 - fromFoldable :: Foldable f => f a -> FMList a
 - null :: FMList a -> Bool
 - length :: FMList a -> Int
 - genericLength :: Num b => FMList a -> b
 - head :: FMList a -> a
 - tail :: FMList a -> FMList a
 - last :: FMList a -> a
 - init :: FMList a -> FMList a
 - reverse :: FMList a -> FMList a
 - toList :: Foldable t => forall a. t a -> [a]
 - flatten :: Foldable t => FMList (t a) -> FMList a
 - foldMapA :: (Foldable t, Applicative f, Monoid m) => (a -> f m) -> t a -> f m
 - filter :: (a -> Bool) -> FMList a -> FMList a
 - take :: (Ord n, Num n) => n -> FMList a -> FMList a
 - drop :: (Ord n, Num n) => n -> FMList a -> FMList a
 - takeWhile :: (a -> Bool) -> FMList a -> FMList a
 - dropWhile :: (a -> Bool) -> FMList a -> FMList a
 - zip :: FMList a -> FMList b -> FMList (a, b)
 - zipWith :: (a -> b -> c) -> FMList a -> FMList b -> FMList c
 - iterate :: (a -> a) -> a -> FMList a
 - repeat :: a -> FMList a
 - cycle :: FMList a -> FMList a
 - unfold :: (b -> FMList (Either b a)) -> b -> FMList a
 - unfoldr :: (b -> Maybe (a, b)) -> b -> FMList a
 
Documentation
transform :: (forall m. Monoid m => (a -> m) -> b -> m) -> FMList b -> FMList a Source #
The function transform transforms a list by changing
 the map function that is passed to foldMap.
It has the following property:
transform a . transform b = transform (b . a)
For example:
m >>= g
= flatten (fmap g m)
= flatten . fmap g $ m
= transform foldMap . transform (. g) $ m
= transform ((. g) . foldMap) m
= transform (\f -> foldMap f . g) m
Construction
empty :: Alternative f => forall a. f a #
The identity of <|>
fromFoldable :: Foldable f => f a -> FMList a Source #
Basic functions
genericLength :: Num b => FMList a -> b Source #
Folding
foldMapA :: (Foldable t, Applicative f, Monoid m) => (a -> f m) -> t a -> f m Source #
Map each element of a structure to an action, evaluate these actions from left to right, and concat the monoid results.
Unfolding
repeat :: a -> FMList a Source #
repeat buids an infinite list of a single value.
 While infinite, the result is still accessible from both the start and end.
cycle :: FMList a -> FMList a Source #
cycle repeats a list to create an infinite list.
 It is also accessible from the end, where last (cycle l) equals last l.
unfold :: (b -> FMList (Either b a)) -> b -> FMList a Source #
unfold builds a list from a seed value.
 The function takes the seed and returns an FMList of values.
 If the value is Right a, then a is appended to the result, and if the
 value is Left b, then b is used as seed value in a recursive call.
A simple use of unfold (simulating unfoldl):
*> unfold (\b -> if b == 0 then empty else Left (b-1) `pair` Right b) 10 fromList [1,2,3,4,5,6,7,8,9,10]
unfoldr :: (b -> Maybe (a, b)) -> b -> FMList a Source #
unfoldr builds an FMList from a seed value from left to right.
 The function takes the element and returns Nothing
 if it is done producing the list or returns Just (a,b), in which
 case, a is a appended to the result and b is used as the next
 seed value in a recursive call.
A simple use of unfoldr:
*> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10 fromList [10,9,8,7,6,5,4,3,2,1]