map-reduce-folds-0.1.0.4: foldl wrappers for map-reduce

Copyright(c) Adam Conner-Sax 2019
LicenseBSD-3-Clause
Maintaineradam_conner_sax@yahoo.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.MapReduce.Simple

Contents

Description

Helper functions and default Engines and grouping functions for assembling map/reduce folds.

Synopsis

Unpackers

noUnpack :: Unpack x x Source #

Don't do anything in the unpacking stage

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

mapReduceFold Source #

Arguments

:: Ord k 
=> Unpack x y

unpack x to none or one or many y's

-> Assign k y c

assign each y to a key value pair (k,c)

-> Reduce k c d

reduce a grouped [c] to d

-> Fold x [d] 

mapReduceFoldM Source #

Arguments

:: (Monad m, Ord k) 
=> UnpackM m x y

unpack x to none or one or many y's

-> AssignM m k y c

assign each y to a key value pair (k,c)

-> ReduceM m k c d

reduce a grouped [c] to d

-> FoldM m x [d] 

hashableMapReduceFold Source #

Arguments

:: (Hashable k, Eq k) 
=> Unpack x y

unpack x to none or one or many y's

-> Assign k y c

assign each y to a key value pair (k,c)

-> Reduce k c d

reduce a grouped [c] to d

-> Fold x [d] 

hashableMapReduceFoldM Source #

Arguments

:: (Monad m, Hashable k, Eq k) 
=> UnpackM m x y

unpack x to to none or one or many y's

-> AssignM m k y c

assign each y to a key value pair (k,c)

-> ReduceM m k c d

reduce a grouped [c] to d

-> FoldM m x [d] 

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

class Hashable a #

The class of types that can be converted to a hash value.

Minimal implementation: hashWithSalt.

Instances
Hashable Bool 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

Hashable Char 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

Hashable Double 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Hashable Float 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Hashable Int 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

Hashable Ordering 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

Hashable Word 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Hashable SomeTypeRep 
Instance details

Defined in Data.Hashable.Class

Hashable () 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> () -> Int #

hash :: () -> Int #

Hashable BigNat 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> BigNat -> Int #

hash :: BigNat -> Int #

Hashable Void 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Void -> Int #

hash :: Void -> Int #

Hashable Unique 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Unique -> Int #

hash :: Unique -> Int #

Hashable Version 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Version -> Int #

hash :: Version -> Int #

Hashable ThreadId 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> ThreadId -> Int #

hash :: ThreadId -> Int #

Hashable WordPtr 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> WordPtr -> Int #

hash :: WordPtr -> Int #

Hashable IntPtr 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> IntPtr -> Int #

hash :: IntPtr -> Int #

Hashable ShortByteString 
Instance details

Defined in Data.Hashable.Class

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable a => Hashable [a] 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> [a] -> Int #

hash :: [a] -> Int #

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

Hashable a => Hashable (Ratio a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ratio a -> Int #

hash :: Ratio a -> Int #

Hashable (Ptr a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ptr a -> Int #

hash :: Ptr a -> Int #

Hashable (FunPtr a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> FunPtr a -> Int #

hash :: FunPtr a -> Int #

Hashable a => Hashable (Complex a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Complex a -> Int #

hash :: Complex a -> Int #

Hashable (Fixed a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Fixed a -> Int #

hash :: Fixed a -> Int #

Hashable a => Hashable (Min a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Min a -> Int #

hash :: Min a -> Int #

Hashable a => Hashable (Max a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Max a -> Int #

hash :: Max a -> Int #

Hashable a => Hashable (First a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> First a -> Int #

hash :: First a -> Int #

Hashable a => Hashable (Last a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Last a -> Int #

hash :: Last a -> Int #

Hashable a => Hashable (WrappedMonoid a) 
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable (Option a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Option a -> Int #

hash :: Option a -> Int #

Hashable (StableName a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> StableName a -> Int #

hash :: StableName a -> Int #

Hashable a => Hashable (Identity a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Identity a -> Int #

hash :: Identity a -> Int #

Hashable a => Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

Hashable (Hashed a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Hashed a -> Int #

hash :: Hashed a -> Int #

Hashable a => Hashable (HashSet a) 
Instance details

Defined in Data.HashSet.Base

Methods

hashWithSalt :: Int -> HashSet a -> Int #

hash :: HashSet a -> Int #

(Hashable a, Hashable b) => Hashable (Either a b) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Either a b -> Int #

hash :: Either a b -> Int #

Hashable (TypeRep a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> TypeRep a -> Int #

hash :: TypeRep a -> Int #

(Hashable a1, Hashable a2) => Hashable (a1, a2) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2) -> Int #

hash :: (a1, a2) -> Int #

(Hashable a, Hashable b) => Hashable (Arg a b) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Arg a b -> Int #

hash :: Arg a b -> Int #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

(Hashable k, Hashable v) => Hashable (HashMap k v) 
Instance details

Defined in Data.HashMap.Base

Methods

hashWithSalt :: Int -> HashMap k v -> Int #

hash :: HashMap k v -> Int #

(Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3) -> Int #

hash :: (a1, a2, a3) -> Int #

Hashable a => Hashable (Const a b) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Const a b -> Int #

hash :: Const a b -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4) -> Int #

hash :: (a1, a2, a3, a4) -> Int #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Product f g a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Product f g a -> Int #

hash :: Product f g a -> Int #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Sum f g a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Sum f g a -> Int #

hash :: Sum f g a -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5) -> Int #

hash :: (a1, a2, a3, a4, a5) -> Int #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Compose f g a)

In general, hash (Compose x) ≠ hash x. However, hashWithSalt satisfies its variant of this equivalence.

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Compose f g a -> Int #

hash :: Compose f g a -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6) -> Int #

hash :: (a1, a2, a3, a4, a5, a6) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6, a7) -> Int #

hash :: (a1, a2, a3, a4, a5, a6, a7) -> Int #