transient-universe-0.4.1: Remote execution and map-reduce: distributed computing for Transient

Safe HaskellNone
LanguageHaskell2010

Transient.MapReduce

Contents

Synopsis

Documentation

class (Foldable c, Typeable c, Typeable a, Monoid (c a), Loggable (c a)) => Distributable c a where Source #

Minimal complete definition

singleton, splitAt, fromList

Methods

singleton :: a -> c a Source #

splitAt :: Int -> c a -> (c a, c a) Source #

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

Instances

distribute :: (Loggable a, Distributable vector a) => vector a -> DDS (vector a) Source #

distribute a vector of values among many nodes. If the vector is static and sharable, better use the get* primitives since each node will load the data independently.

getText :: (Loggable a, Distributable vector a) => (String -> [a]) -> String -> DDS (vector a) Source #

input data from a text that must be static and shared by all the nodes. The function parameter partition the text in words

getUrl :: (Loggable a, Distributable vector a) => (String -> [a]) -> String -> DDS (vector a) Source #

generate a DDS from the content of a URL. The first parameter is a function that divide the text in words

getFile :: (Loggable a, Distributable vector a) => (String -> [a]) -> String -> DDS (vector a) Source #

generate a DDS from a file. All the nodes must access the file with the same path the first parameter is the parser that generates elements from the content

textUrl :: String -> DDS (Vector Text) Source #

get the worlds of an URL

textFile :: String -> DDS (Vector Text) Source #

get the words of a file

mapKeyB :: (Loggable a, Loggable b, Loggable k, Ord k) => (a -> (k, b)) -> DDS (Vector a) -> DDS (Map k (Vector b)) Source #

perform a map and partition the result with different keys using boxed vectors The final result will be used by reduce.

mapKeyU :: (Loggable a, Unbox a, Loggable b, Unbox b, Loggable k, Ord k) => (a -> (k, b)) -> DDS (Vector a) -> DDS (Map k (Vector b)) Source #

perform a map and partition the result with different keys using unboxed vectors The final result will be used by reduce.

reduce :: (Hashable k, Ord k, Distributable vector a, Loggable k, Loggable a) => (a -> a -> a) -> DDS (Map k (vector a)) -> Cloud (Map k a) Source #

eval :: DDS a -> Cloud (PartRef a) Source #

Orphan instances

Foldable Vector Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Vector a -> [a] #

null :: Vector a -> Bool #

length :: Vector a -> Int #

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

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

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

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

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