Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (Foldable c, Monoid (c a), Loggable (c a), Typeable c, Typeable a) => Distributable c a where
- distribute :: (Loggable a, Distributable container a) => container a -> DDS (container a)
- getText :: (Loggable a, Distributable container a) => (String -> [a]) -> String -> DDS (container a)
- getUrl :: (Loggable a, Distributable container a) => (String -> [a]) -> String -> DDS (container a)
- getFile :: (Loggable a, Distributable container a) => (String -> [a]) -> String -> DDS (container a)
- textUrl :: String -> DDS (Vector Text)
- textFile :: String -> DDS (Vector Text)
- 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))
- 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))
- 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)
- 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, Monoid (c a), Loggable (c a), Typeable c, Typeable a) => Distributable c a where 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
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
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.
the chunk of data loaded in memory
Instances
Read a => Read (Partition a) Source # | |
Show a => Show (Partition a) Source # | |
Indexable (Partition a) Source # | |
Loggable a => IResource (Partition a) Source # | |
Defined in Transient.MapReduce keyResource :: Partition a -> String # readResourceByKey :: String -> IO (Maybe (Partition a)) # readResourcesByKey :: [String] -> IO [Maybe (Partition a)] # readResource :: Partition a -> IO (Maybe (Partition a)) # writeResource :: Partition a -> IO () # writeResources :: [Partition a] -> IO () # delResource :: Partition a -> IO () # delResources :: [Partition a] -> IO () # |
a link to a chunk of data, located in a node
Orphan instances
Foldable Vector Source # | |
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 # elem :: Eq a => a -> Vector a -> Bool # maximum :: Ord a => Vector a -> a # minimum :: Ord a => Vector a -> a # | |
Loggable Text Source # | |
serialize :: Text -> Builder # deserializePure :: ByteString -> Maybe (Text, ByteString) # deserialize :: TransIO Text # | |
(Loggable a, Unbox a) => Loggable (Vector a) Source # | |
serialize :: Vector a -> Builder # deserializePure :: ByteString -> Maybe (Vector a, ByteString) # deserialize :: TransIO (Vector a) # | |
Loggable a => Loggable (Vector a) Source # | |
serialize :: Vector a -> Builder # deserializePure :: ByteString -> Maybe (Vector a, ByteString) # deserialize :: TransIO (Vector a) # |