fmlist-0.8: FoldMap lists

Portabilityportable
Stabilityexperimental
Maintainersjoerd@w3future.com

Data.FMList

Contents

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

Synopsis

Documentation

newtype FMList a Source

FMList is a foldMap function wrapped up in a newtype.

Constructors

FM 

Fields

unFM :: forall m. Monoid m => (a -> m) -> m
 

transform :: (forall m. Monoid m => (a -> m) -> b -> m) -> FMList b -> FMList aSource

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 <|>

cons :: a -> FMList a -> FMList aSource

snoc :: FMList a -> a -> FMList aSource

pair :: a -> a -> FMList aSource

Basic functions

head :: FMList a -> aSource

last :: FMList a -> aSource

Folding

toList :: Foldable t => t a -> [a]

List of elements of a structure.

flatten :: Foldable t => FMList (t a) -> FMList aSource

foldMapA :: (Foldable t, Applicative f, Monoid m) => (a -> f m) -> t a -> f mSource

Map each element of a structure to an action, evaluate these actions from left to right, and concat the monoid results.

filter :: (a -> Bool) -> FMList a -> FMList aSource

take :: (Ord n, Num n) => n -> FMList a -> FMList aSource

drop :: (Ord n, Num n) => n -> FMList a -> FMList aSource

takeWhile :: (a -> Bool) -> FMList a -> FMList aSource

dropWhile :: (a -> Bool) -> FMList a -> FMList aSource

zip :: FMList a -> FMList b -> FMList (a, b)Source

zipWith :: (a -> b -> c) -> FMList a -> FMList b -> FMList cSource

Unfolding

iterate :: (a -> a) -> a -> FMList aSource

unfold :: (b -> FMList (Either b a)) -> b -> FMList aSource

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 aSource

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]