Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class (Foldable c, Typeable c, Typeable a, Monoid (c a), Loggable (c a)) => Distributable c a where
- distribute :: (Loggable a, Distributable vector a) => vector a -> DDS (vector a)
- getText :: (Loggable a, Distributable vector a) => (String -> [a]) -> String -> DDS (vector a)
- getUrl :: (Loggable a, Distributable vector a) => (String -> [a]) -> String -> DDS (vector a)
- getFile :: (Loggable a, Distributable vector a) => (String -> [a]) -> String -> DDS (vector a)
- textUrl :: String -> DDS (Vector Text)
- textFile :: String -> DDS (Vector Text)
- mapKeyB :: (Loggable a, Loggable b, Loggable k, Ord k) => (a -> (k, b)) -> DDS (Vector a) -> DDS (Map k (Vector b))
- mapKeyU :: (Loggable a, Unbox a, Loggable b, Unbox b, Loggable k, Ord k) => (a -> (k, b)) -> DDS (Vector a) -> DDS (Map k (Vector b))
- reduce :: (Hashable k, Ord k, Distributable vector a, Loggable k, Loggable a) => (a -> a -> a) -> DDS (Map k (vector a)) -> Cloud (Map k a)
- eval :: DDS a -> Cloud (PartRef a)
- data DDS a = Loggable a => DDS (Cloud (PartRef a))
- data Partition a = Part Node Path Save a
- data PartRef a = Ref Node Path Save
Documentation
class (Foldable c, Typeable c, Typeable a, Monoid (c a), Loggable (c a)) => Distributable c a where Source #
(Loggable a, Unbox a) => Distributable Vector a Source # | |
Loggable a => Distributable Vector a Source # | |
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
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 #