fmlist-0.9.2: FoldMap lists

Copyright(c) Sjoerd Visscher 2009
LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

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

Instances

Monad FMList Source # 

Methods

(>>=) :: FMList a -> (a -> FMList b) -> FMList b #

(>>) :: FMList a -> FMList b -> FMList b #

return :: a -> FMList a #

fail :: String -> FMList a #

Functor FMList Source # 

Methods

fmap :: (a -> b) -> FMList a -> FMList b #

(<$) :: a -> FMList b -> FMList a #

Applicative FMList Source # 

Methods

pure :: a -> FMList a #

(<*>) :: FMList (a -> b) -> FMList a -> FMList b #

liftA2 :: (a -> b -> c) -> FMList a -> FMList b -> FMList c #

(*>) :: FMList a -> FMList b -> FMList b #

(<*) :: FMList a -> FMList b -> FMList a #

Foldable FMList Source # 

Methods

fold :: Monoid m => FMList m -> m #

foldMap :: Monoid m => (a -> m) -> FMList a -> m #

foldr :: (a -> b -> b) -> b -> FMList a -> b #

foldr' :: (a -> b -> b) -> b -> FMList a -> b #

foldl :: (b -> a -> b) -> b -> FMList a -> b #

foldl' :: (b -> a -> b) -> b -> FMList a -> b #

foldr1 :: (a -> a -> a) -> FMList a -> a #

foldl1 :: (a -> a -> a) -> FMList a -> a #

toList :: FMList a -> [a] #

null :: FMList a -> Bool #

length :: FMList a -> Int #

elem :: Eq a => a -> FMList a -> Bool #

maximum :: Ord a => FMList a -> a #

minimum :: Ord a => FMList a -> a #

sum :: Num a => FMList a -> a #

product :: Num a => FMList a -> a #

Traversable FMList Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FMList a -> f (FMList b) #

sequenceA :: Applicative f => FMList (f a) -> f (FMList a) #

mapM :: Monad m => (a -> m b) -> FMList a -> m (FMList b) #

sequence :: Monad m => FMList (m a) -> m (FMList a) #

Alternative FMList Source # 

Methods

empty :: FMList a #

(<|>) :: FMList a -> FMList a -> FMList a #

some :: FMList a -> FMList [a] #

many :: FMList a -> FMList [a] #

MonadPlus FMList Source # 

Methods

mzero :: FMList a #

mplus :: FMList a -> FMList a -> FMList a #

Show a => Show (FMList a) Source # 

Methods

showsPrec :: Int -> FMList a -> ShowS #

show :: FMList a -> String #

showList :: [FMList a] -> ShowS #

Semigroup (FMList a) Source # 

Methods

(<>) :: FMList a -> FMList a -> FMList a #

sconcat :: NonEmpty (FMList a) -> FMList a #

stimes :: Integral b => b -> FMList a -> FMList a #

Monoid (FMList a) Source # 

Methods

mempty :: FMList a #

mappend :: FMList a -> FMList a -> FMList a #

mconcat :: [FMList a] -> FMList a #

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

cons :: a -> FMList a -> FMList a Source #

snoc :: FMList a -> a -> FMList a Source #

pair :: a -> a -> FMList a Source #

fromList :: [a] -> FMList a Source #

Basic functions

head :: FMList a -> a Source #

last :: FMList a -> a Source #

Folding

toList :: Foldable t => forall a. t a -> [a] #

List of elements of a structure, from left to right.

flatten :: Foldable t => FMList (t a) -> FMList a Source #

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.

filter :: (a -> Bool) -> FMList a -> FMList a Source #

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

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

takeWhile :: (a -> Bool) -> FMList a -> FMList a Source #

dropWhile :: (a -> Bool) -> FMList a -> FMList a Source #

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

zipWith :: (a -> b -> c) -> FMList a -> FMList b -> FMList c Source #

Unfolding

iterate :: (a -> a) -> a -> FMList a Source #

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]