transient-universe-0.6.0.1: fully composable remote execution for the creation of distributed systems

Safe HaskellNone
LanguageHaskell2010

Transient.MapReduce

Contents

Synopsis

Documentation

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

Methods

singleton :: a -> c a Source #

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

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

Instances
(Typeable a, Loggable a, Unbox a) => Distributable Vector a Source # 
Instance details

Defined in Transient.MapReduce

Methods

singleton :: a -> Vector a Source #

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

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

(Typeable a, Loggable a) => Distributable Vector a Source # 
Instance details

Defined in Transient.MapReduce

Methods

singleton :: a -> Vector a Source #

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

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

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

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

getText :: (Loggable a, Distributable container a) => (String -> [a]) -> String -> DDS (container 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 container a) => (String -> [a]) -> String -> DDS (container 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 container a) => (String -> [a]) -> String -> DDS (container 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 :: (Typeable a, Loggable a, Typeable b, Loggable b, Typeable k, 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 :: (Typeable a, Loggable a, Unbox a, Typeable b, Loggable b, Unbox b, Typeable k, 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 container a, Typeable k, Loggable k, Typeable a, Loggable a) => (a -> a -> a) -> DDS (Map k (container a)) -> Cloud (Map k a) Source #

internals

data DDS a Source #

a DDS contains a distrib. computation which return a (non-deterministicstreamset of) links to the generated chunks of data, in different nodes, thanks to the non-deterministic and multithreaded nature of the Transient/Cloud comp.

Constructors

Loggable a => DDS (Cloud (PartRef a)) 

data Partition a Source #

the chunk of data loaded in memory

Constructors

Part Node Path Save a 
Instances
Read a => Read (Partition a) Source # 
Instance details

Defined in Transient.MapReduce

Show a => Show (Partition a) Source # 
Instance details

Defined in Transient.MapReduce

Indexable (Partition a) Source # 
Instance details

Defined in Transient.MapReduce

Methods

key :: Partition a -> String #

defPath :: Partition a -> String #

Loggable a => IResource (Partition a) Source # 
Instance details

Defined in Transient.MapReduce

data PartRef a Source #

a link to a chunk of data, located in a node

Constructors

Ref Node Path Save 
Instances
Read (PartRef a) Source # 
Instance details

Defined in Transient.MapReduce

Show (PartRef a) Source # 
Instance details

Defined in Transient.MapReduce

Methods

showsPrec :: Int -> PartRef a -> ShowS #

show :: PartRef a -> String #

showList :: [PartRef a] -> ShowS #

Typeable a => Loggable (PartRef a) Source # 
Instance details

Defined in Transient.MapReduce

Orphan instances

Foldable Vector Source # 
Instance details

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 #

Loggable Text Source # 
Instance details

(Loggable a, Unbox a) => Loggable (Vector a) Source # 
Instance details

Loggable a => Loggable (Vector a) Source # 
Instance details