Copyright | (c) Abhinav Gupta 2015 |
---|---|
License | BSD3 |
Maintainer | Abhinav Gupta <mail@abhinavg.net> |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Implements a representation of a list as a fold over it.
Synopsis
- data FoldList a
- map :: (a -> b) -> FoldList a -> FoldList b
- replicate :: Int -> a -> FoldList a
- replicateM :: Monad m => Int -> m a -> m (FoldList a)
- foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- toList :: Foldable t => t a -> [a]
- fromFoldable :: Foldable f => f a -> FoldList a
- fromMap :: (forall r. (r -> k -> v -> r) -> r -> m k v -> r) -> m k v -> FoldList (k, v)
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
Documentation
FoldList represents a list as a foldl'
traversal over it.
This allows us to avoid allocating new collections for an intermediate representation of various data types that users provide.
Instances
Functor FoldList Source # | |
Foldable FoldList Source # | |
Defined in Pinch.Internal.FoldList fold :: Monoid m => FoldList m -> m # foldMap :: Monoid m => (a -> m) -> FoldList a -> m # foldr :: (a -> b -> b) -> b -> FoldList a -> b # foldr' :: (a -> b -> b) -> b -> FoldList a -> b # foldl :: (b -> a -> b) -> b -> FoldList a -> b # foldl' :: (b -> a -> b) -> b -> FoldList a -> b # foldr1 :: (a -> a -> a) -> FoldList a -> a # foldl1 :: (a -> a -> a) -> FoldList a -> a # elem :: Eq a => a -> FoldList a -> Bool # maximum :: Ord a => FoldList a -> a # minimum :: Ord a => FoldList a -> a # | |
Traversable FoldList Source # | |
Eq a => Eq (FoldList a) Source # | |
Show a => Show (FoldList a) Source # | |
Semigroup (FoldList a) Source # | |
Monoid (FoldList a) Source # | |
NFData a => NFData (FoldList a) Source # | |
Defined in Pinch.Internal.FoldList | |
Hashable a => Hashable (FoldList a) Source # | |
Defined in Pinch.Internal.FoldList |
map :: (a -> b) -> FoldList a -> FoldList b Source #
Applies the given function to all elements in the FoldList.
Note that the function is applied lazily when the results are requested. If the results of the same FoldList are requested multiple times, the function will be called multiple times on the same elements.
replicate :: Int -> a -> FoldList a Source #
Returns a FoldList with the given item repeated n
times.
replicateM :: Monad m => Int -> m a -> m (FoldList a) Source #
Executes the given monadic action the given number of times and returns a FoldList of the results.
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to weak head normal
form before being applied, avoiding the collection of thunks that would
otherwise occur. This is often what you want to strictly reduce a finite
list to a single, monolithic result (e.g. length
).
For a general Foldable
structure this should be semantically identical
to,
foldl f z =foldl'
f z .toList
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b #
Right-associative fold of a structure.
In the case of lists, foldr
, when applied to a binary operator, a
starting value (typically the right-identity of the operator), and a
list, reduces the list using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Note that, since the head of the resulting expression is produced by
an application of the operator to the first element of the list,
foldr
can produce a terminating expression from an infinite list.
For a general Foldable
structure this should be semantically identical
to,
foldr f z =foldr
f z .toList
fromFoldable :: Foldable f => f a -> FoldList a Source #
Builds a FoldList from a Foldable.
:: (forall r. (r -> k -> v -> r) -> r -> m k v -> r) |
|
-> m k v | |
-> FoldList (k, v) |
Builds a FoldList over pairs of items of a map.
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.