Portability | portable |
---|---|
Stability | experimental |
Maintainer | sjoerd |
FoldMap lists: lists represented by their foldMap function.
- newtype FMList a = FM {}
- transform :: (forall b. Monoid b => (a -> b) -> c -> b) -> FMList c -> 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
- append :: FMList a -> FMList a -> FMList a
- toList :: Foldable t => t a -> [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
- flatten :: FMList (FMList a) -> FMList a
- 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
- unfoldr :: (b -> Maybe (a, b)) -> b -> FMList a
- unfoldl :: (b -> Maybe (b, a)) -> b -> FMList a
Documentation
FMList is a foldMap function wrapped up in a newtype. 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
transform :: (forall b. Monoid b => (a -> b) -> c -> b) -> FMList c -> FMList aSource
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 aSource
Basic functions
genericLength :: Num b => FMList a -> bSource