Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module exports a bunch of common folds.
For the classic example
import Control.Applicative import qualified Data.Fold.Common as C avg :: C.L' Double Double avg = (/) <$> C.sum <*> C.count main :: IO () main = print $ C.run [1 .. 10000000] avg
This will run in constant memory as we'd hope. In general the
rules for keeping memory usage low while using folds
are
- Don't try to consume a left fold lazily
- Don't try to consume a right fold strictly
- Never use
>>=
- Never use
prefix
on right folds - Never use
postfix
on left folds
Also note that monoidal folds can be combined with strict left ones
with strictify
.
- module Data.Fold
- sum :: Num a => L' a a
- product :: Num a => L' a a
- count :: Enum e => L' a e
- mconcat :: Monoid m => L' m m
- minimum :: Ord a => L' a (Maybe a)
- maximum :: Ord a => L' a (Maybe a)
- nub :: Ord a => L' a [a]
- slowNub :: Eq a => L' a [a]
- intoSet :: Ord a => L' a (Set a)
- last :: L' a (Maybe a)
- nth :: (Eq b, Ord b, Num b) => b -> L' a (Maybe a)
- any :: (a -> Bool) -> M a Bool
- all :: (a -> Bool) -> M a Bool
- and :: M Bool Bool
- or :: M Bool Bool
- elem :: Eq a => a -> M a Bool
- notElem :: Eq a => a -> M a Bool
- find :: (a -> Bool) -> M a (Maybe a)
- head :: M a (Maybe a)
- null :: M a Bool
- strictify :: M a b -> L' a b
- intoList :: R a [a]
- take :: (Eq b, Ord b, Num b) => b -> R a [a]
- drop :: (Eq b, Ord b, Num b) => b -> R a [a]
- indexOf :: Enum e => (a -> Bool) -> R a (Maybe e)
- chunk :: (Show b, Eq b) => (a -> b) -> R a [[a]]
- concat :: R [a] [a]
Documentation
module Data.Fold
Left Folds
count :: Enum e => L' a e Source
Count the number of elements fed to a fold
>>>
run [1 .. 10] count
10
Note: GHCi will default Enum e
to ()
. If you see
*** Exception: Prelude.Enum.().succ: bad argument
You've been bitten by this.
mconcat :: Monoid m => L' m m Source
mappend
all the elements of a sequence together.
>>>
run [[1, 2, 3, 4], [5, 6, 7, 8]] mconcat
[1, 2, 3, 4, 5, 6, 7, 8]
>>>
run (map Sum [1, 2, 3, 4]) mconcat
Sum {getSum = 10}
minimum :: Ord a => L' a (Maybe a) Source
Minimum of all inputs. If no inputs are supplied this returns
Nothing
.
>>>
run [1, 2, 3] minimum
1>>>
run [1 ..] minimum
... diverges ...
maximum :: Ord a => L' a (Maybe a) Source
Maximum of all inputs. If no inputs are supplied this returns
Nothing
.
>>>
run [1, 2, 3] maximum
3
>>>
run [1 ..] maximum
... diverges ...
nub :: Ord a => L' a [a] Source
De-duplicate all the inputs while preserving order. O(n log(n))
>>>
run (replicate 10 1 ++ replicate 10 2) nub
[1, 2]
>>>
run [1, 2, 1] nub
[1, 2]
intoSet :: Ord a => L' a (Set a) Source
Collect all members into a Set
.
>>>
run [1 .. 10] intoSet
fromList [1, 2, 3, 4, 5, 6, 7, 8, 9, 10]
Grab the last element inputted
>>>
run [1 .. 10] last
Just 10
>>>
run [] last
Nothing
nth :: (Eq b, Ord b, Num b) => b -> L' a (Maybe a) Source
Grab the nth element inputted.
>>>
run [1 .. 10] (nth 5)
Just 6
>>>
run [1 .. 10] (nth 20)
Nothing
Monoidal Folds
any :: (a -> Bool) -> M a Bool Source
Check that if predicate holds for any inputs to the fold.
>>>
run [1, 2, 3, 4] (any even)
True
>>>
run [] (any $ const False)
False
all :: (a -> Bool) -> M a Bool Source
Check that if predicate holds for all inputs to the fold.
>>>
run [1, 2, 3, 4] (all (< 6))
True
>>>
run [1, 2, 3, 4] (all (> 1))
False
Check whether all elements are True
.
>>>
run (repeat False) and
False
>>>
run (repeat True) and
... diverges ...
Check whether any elements are True
.
>>>
run (True : repeat False) or
True>>>
run (repeat False) or
... diverges ...
elem :: Eq a => a -> M a Bool Source
Check whether an element is fed into the fold.
>>>
run [1, 2, 3] (elem 3)
True
>>>
run [] (elem 1)
False
notElem :: Eq a => a -> M a Bool Source
Check whther an element isn't fed into the fold. >>> run [1, 2, 3] (notElem 3) False
>>>
run [] (notElem 1)
True
find :: (a -> Bool) -> M a (Maybe a) Source
Find the first element for which a predicate holds.
>>>
run [1, 2, 3, 4] (find even)
Just 2
>>>
run [1, 2, 3, 4] (find (> 4))
Nothing
Grab the first inputted element.
>>>
run [1 ..] head
Just 1
>>>
run [] head
Nothing
Check whether a fold was fed any elements.
>>>
run [] null
True
>>>
run [1..] null
False
strictify :: M a b -> L' a b Source
Occasionally we want to use a short-circuiting fold with other,
nonlazy folds. This function drops laziness on the floor for a L'
fold. This is dangerous because it can potentially effect
termination behavior.
>>>
run (repeat False) and
False
>>>
run (repeat False) (strictify and)
... diverges ...
This is generally an advantage when we want to combine a monoidal fold with a left one.
>>>
run [1.0, 2, 3, 4] $ (/) <$> strictify head <*> maximum
0.25
Right Folds
An extremely boring fold. You can almost view this as an identity fold across lists.
>>>
run [1 .. 10] intoLists
[1, 2, 3, 4, 5, 6, 7, 8, 9, 10]
take :: (Eq b, Ord b, Num b) => b -> R a [a] Source
Take the first n
inputs to the fold. If less then n
inputs
are fed in total then take as many as possible.
>>>
run [1 .. 10] (take 3)
[1, 2, 3]
>>>
run [1, 2, 3] (take 100)
[1, 2, 3]
drop :: (Eq b, Ord b, Num b) => b -> R a [a] Source
Drop the first n
items. If less then n
items are supplied
then return the empty list.
>>>
run [1, 2, 3] (drop 1)
[2, 3]
>>>
run [1, 2, 3] (drop 100)
[]
indexOf :: Enum e => (a -> Bool) -> R a (Maybe e) Source
Find the first index for which a predicate holds.
>>>
run [1, 2, 3, 4] (indexOf (== 4))
Just 3
>>>
run [1, 2, 3, 4] (indexOf (> 4))
Nothing
chunk :: (Show b, Eq b) => (a -> b) -> R a [[a]] Source
Chunk the input into partitions according to a function. While the values from the function are equal elements are collected into a chunk. Note that partitioning according to a predicate is just a special case of this.
>>>
run [1, 1, 2, 3] (chunk id)
[[1, 1], [2], [3]]
>>>
run [1, -1, 2, 1] (chunk abs)
[[1, -1], 2, [1]]
>>>
run [1, 2, 4, 6, 5] (chunk even)
[[1], [2, 4, 6], 5]
Lazily produce a flattened list of the inputted lists.
>>>
run [[1], [2], [3]] concat
[1, 2, 3]
>>>
head $ run (map return [1..]) concat
1
Note: The right fold ensures that all applications of ++
associate to the right. This makes this fold ideal for streaming
but slow when completely forced.