Holumbus-MapReduce-0.1.1: a distributed MapReduce framework

Portabilityportable
Stabilityexperimental
MaintainerStefan Schmidt (stefanschmidt@web.de)

Holumbus.MapReduce.Types

Contents

Description

Version : 0.1

Synopsis

Documentation

class Hash a whereSource

Methods

hash :: Int -> a -> IntSource

Instances

hashedPartition :: (Hash k2, Binary k2, Binary v2, NFData k2, NFData v2) => MapPartition a k2 v2Source

TaskData

type TaskId = IntegerSource

the task id (should be unique in the system)

data TaskType Source

which type (map, combine, reduce)

data TaskData Source

the TaskData, contains all information to do the task

JobData

type JobId = IntegerSource

the job id (should be unique in the system)

data JobInfo Source

defines a job, this is all data the user has to give to run a job

data JobData Source

the job data, include the user-input and some additional control-data

Instances

data JobResult Source

the result of the job, given by the master

Constructors

JobResult 

Fields

jr_Output :: [FunctionData]
 

TaskAction

data ActionEnvironment Source

the ActionEnvironment contains all data that might be needed during an action. So far, it only keeps the current task data and a reference to the global filesystem and the options. This is a good place to implement counters for the map-reduce-system or other stuff...

type InputReader k1 v1 = ByteString -> IO [(k1, v1)]Source

type OutputWriter k2 v2 = [(k2, v2)] -> IO ByteStringSource

defaultMerge :: (Ord k2, Binary k2, Binary v2) => ReduceMerge a k2 v2Source

readConnector :: (NFData k1, NFData v1, Binary k1, Binary v1) => InputReader k1 v1 -> ActionEnvironment -> [FunctionData] -> IO [(k1, v1)]Source

writeConnector :: (Binary k2, Binary v2) => OutputWriter k2 v2 -> ActionEnvironment -> [(Int, [(k2, v2)])] -> IO [(Int, [FunctionData])]Source

data ActionConfiguration a k1 v1 k2 v2 v3 v4 Source

Constructors

ActionConfiguration 

Fields

ac_Name :: ActionName
 
ac_Info :: ActionInfo
 
ac_OptEncoder :: OptionsEncoder a
 
ac_OptDecoder :: OptionsDecoder a
 
ac_InputEncoder :: InputEncoder k1 v1
 
ac_OutputDecoder :: OutputDecoder k2 v4
 
ac_Split :: Maybe (SplitConfiguration a k1 v1)
 
ac_Map :: Maybe (MapConfiguration a k1 v1 k2 v2)
 
ac_Combine :: Maybe (ReduceConfiguration a k2 v2 v3)
 
ac_Reduce :: Maybe (ReduceConfiguration a k2 v3 v4)
 

data SplitConfiguration a k1 v1 Source

Constructors

SplitConfiguration 

Fields

sc_Function :: SplitFunction a k1 v1
 
sc_Reader :: InputReader k1 v1
 
sc_Writer :: OutputWriter k1 v1
 

data MapConfiguration a k1 v1 k2 v2 Source

Constructors

MapConfiguration 

Fields

mc_Function :: MapFunction a k1 v1 k2 v2
 
mc_Partition :: MapPartition a k2 v2
 
mc_Reader :: InputReader k1 v1
 
mc_Writer :: OutputWriter k2 v2
 

data ReduceConfiguration a k2 v3 v4 Source

Constructors

ReduceConfiguration 

Fields

rc_Merge :: ReduceMerge a k2 v3
 
rc_Function :: ReduceFunction a k2 v3 v4
 
rc_Partition :: ReducePartition a k2 v4
 
rc_Reader :: InputReader k2 v3
 
rc_Writer :: OutputWriter k2 v4
 

defaultMapConfiguration :: (NFData v1, NFData k1, NFData v2, NFData k2, Ord k2, Binary a, Binary k1, Binary v1, Binary k2, Binary v2) => MapFunction a k1 v1 k2 v2 -> MapConfiguration a k1 v1 k2 v2Source

readActionConfiguration :: (Ord k2, Binary a, Show k1, Show v1, Show k2, Show v2, Show v3, Show v4, NFData k1, NFData v1, NFData k2, NFData v2, NFData v3, Binary k1, Binary v1, Binary k2, Binary v2, Binary v3, Binary v4) => ActionConfiguration a k1 v1 k2 v2 v3 v4 -> ActionDataSource

createJobInfoFromConfigurationSource

Arguments

:: ActionConfiguration a k1 v1 k2 v2 v3 v4 
-> a

options

-> [(k1, v1)]

input (Tuples)

-> [FileId]

input (Files)

-> Int

number of splitters

-> Int

number of mappers

-> Int

number of reducers

-> Int

number of results

-> TaskOutputType

type of the result (file of raw)

-> JobInfo 

createListsFromJobResult :: ActionConfiguration a k1 v1 k2 v2 v3 v4 -> JobResult -> ([(k2, v4)], [FileId])Source

data ActionData Source

Constructors

ActionData 

Fields

ad_Name :: ActionName
 
ad_Info :: ActionInfo
 
ad_Split :: Maybe BinarySplitAction
 
ad_Map :: Maybe BinaryMapAction
 
ad_Combine :: Maybe BinaryReduceAction
 
ad_Reduce :: Maybe BinaryReduceAction
 

MapAction

type MapAction a k1 v1 k2 v2 = ActionEnvironment -> a -> Int -> [(k1, v1)] -> IO [(Int, [(k2, v2)])]Source

general MapAction

type MapFunction a k1 v1 k2 v2 = ActionEnvironment -> a -> k1 -> v1 -> IO [(k2, v2)]Source

type MapPartition a k2 v2 = ActionEnvironment -> a -> Int -> [(k2, v2)] -> IO [(Int, [(k2, v2)])]Source

Combine-Reduce-Action

type ReduceAction a k2 v2 v3 = ActionEnvironment -> a -> Int -> [(k2, v2)] -> IO [(Int, [(k2, v3)])]Source

general MapAction

type ReduceMerge a k2 v2 = ActionEnvironment -> a -> [(k2, v2)] -> IO [(k2, [v2])]Source

type ReduceFunction a k2 v2 v3 = ActionEnvironment -> a -> k2 -> [v2] -> IO (Maybe v3)Source

type ReducePartition a k2 v3 = ActionEnvironment -> a -> Int -> [(k2, v3)] -> IO [(Int, [(k2, v3)])]Source

type SplitFunction a k1 v1 = SplitAction a k1 v1Source

type SplitAction a k1 v1 = ActionEnvironment -> a -> Int -> [(k1, v1)] -> IO [(Int, [(k1, v1)])]Source

general SplitAction