Copyright | (c) Adam Conner-Sax 2019 |
---|---|
License | BSD-3-Clause |
Maintainer | adam_conner_sax@yahoo.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Helper functions and default Engines and grouping functions for assembling map/reduce folds.
Synopsis
- noUnpack :: Unpack x x
- simpleUnpack :: (x -> y) -> Unpack x y
- filterUnpack :: (x -> Bool) -> Unpack x x
- assign :: forall k y c. (y -> k) -> (y -> c) -> Assign k y c
- processAndLabel :: (forall h. (Foldable h, Functor h) => h x -> y) -> (k -> y -> z) -> Reduce k x z
- processAndLabelM :: Monad m => (forall h. (Foldable h, Functor h) => h x -> m y) -> (k -> y -> z) -> ReduceM m k x z
- foldAndLabel :: Fold x y -> (k -> y -> z) -> Reduce k x z
- foldAndLabelM :: Monad m => FoldM m x y -> (k -> y -> z) -> ReduceM m k x z
- reduceMapWithKey :: (k -> y -> z) -> Reduce k x y -> Reduce k x z
- reduceMMapWithKey :: (k -> y -> z) -> ReduceM m k x y -> ReduceM m k x z
- mapReduceFold :: Ord k => Unpack x y -> Assign k y c -> Reduce k c d -> Fold x [d]
- mapReduceFoldM :: (Monad m, Ord k) => UnpackM m x y -> AssignM m k y c -> ReduceM m k c d -> FoldM m x [d]
- hashableMapReduceFold :: (Hashable k, Eq k) => Unpack x y -> Assign k y c -> Reduce k c d -> Fold x [d]
- hashableMapReduceFoldM :: (Monad m, Hashable k, Eq k) => UnpackM m x y -> AssignM m k y c -> ReduceM m k c d -> FoldM m x [d]
- unpackOnlyFold :: Unpack x y -> Fold x [y]
- unpackOnlyFoldM :: Monad m => UnpackM m x y -> FoldM m x [y]
- concatFold :: (Monoid d, Foldable g) => Fold a (g d) -> Fold a d
- concatFoldM :: (Monad m, Monoid d, Foldable g) => FoldM m a (g d) -> FoldM m a d
- module Control.MapReduce.Core
- module Control.MapReduce.Core
- class Hashable a
Unpackers
simpleUnpack :: (x -> y) -> Unpack x y Source #
unpack using the given function
filterUnpack :: (x -> Bool) -> Unpack x x Source #
Filter while unpacking, using the given function
Assigners
assign :: forall k y c. (y -> k) -> (y -> c) -> Assign k y c Source #
Assign via two functions of y
, one that provides the key and one that provides the data to be grouped by that key.
Reducers
The most common case is that the reduction doesn't depend on the key.
These functions combine a key-independent processing step and a labeling step for the four variations of Reduce
.
processAndLabel :: (forall h. (Foldable h, Functor h) => h x -> y) -> (k -> y -> z) -> Reduce k x z Source #
create a Reduce from a function of the grouped data to y and a function from the key and y to the result type
processAndLabelM :: Monad m => (forall h. (Foldable h, Functor h) => h x -> m y) -> (k -> y -> z) -> ReduceM m k x z Source #
create a monadic ReduceM from a function of the grouped data to (m y) and a function from the key and y to the result type
foldAndLabel :: Fold x y -> (k -> y -> z) -> Reduce k x z Source #
create a Reduce from a fold of the grouped data to y and a function from the key and y to the result type
foldAndLabelM :: Monad m => FoldM m x y -> (k -> y -> z) -> ReduceM m k x z Source #
create a monadic ReduceM from a monadic fold of the grouped data to (m y) and a function from the key and y to the result type
Reduce Transformers
reduceMapWithKey :: (k -> y -> z) -> Reduce k x y -> Reduce k x z Source #
map a reduce using the given function of key and reduction result.
reduceMMapWithKey :: (k -> y -> z) -> ReduceM m k x y -> ReduceM m k x z Source #
map a monadic reduction with a (non-monadic) function of the key and reduction result
Default Map-Reduce Folds to []
unpackOnlyFold :: Unpack x y -> Fold x [y] Source #
do only the unpack step.
unpackOnlyFoldM :: Monad m => UnpackM m x y -> FoldM m x [y] Source #
do only the (monadic) unpack step. Use a TypeApplication to specify what to unpack to. As in 'unpackOnlyFoldM @[]'
Simplify Results
concatFold :: (Monoid d, Foldable g) => Fold a (g d) -> Fold a d Source #
The simple fold types return lists of results. Often we want to merge these into some other structure via (<>)
concatFoldM :: (Monad m, Monoid d, Foldable g) => FoldM m a (g d) -> FoldM m a d Source #
The simple fold types return lists of results. Often we want to merge these into some other structure via (<>)
Re-Exports
module Control.MapReduce.Core
module Control.MapReduce.Core
The class of types that can be converted to a hash value.
Minimal implementation: hashWithSalt
.