Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Mapper e m = Mapper (Text -> Either e input) (k -> v -> Text) (ConduitT input (k, v) m ())
- data Reducer e m = Eq k => Reducer (Text -> Either e (k, v)) (res -> Text) (k -> v -> ConduitT v res m ())
- runMapper :: MonadIO m => (Text -> e -> m ()) -> Mapper e m -> m ()
- runMapperWith :: MonadIO m => ConduitT () Text m () -> ConduitT Text Void m () -> (Text -> e -> m ()) -> Mapper e m -> m ()
- runReducer :: MonadIO m => (Text -> e -> m ()) -> Reducer e m -> m ()
- runReducerWith :: MonadIO m => ConduitT () Text m () -> ConduitT Text Void m () -> (Text -> e -> m ()) -> Reducer e m -> m ()
- println :: MonadIO m => Text -> m ()
- incCounter :: MonadIO m => Text -> Text -> m ()
- incCounterBy :: MonadIO m => Int -> Text -> Text -> m ()
- sourceHandle :: MonadIO m => Handle -> ConduitT i Text m ()
- sinkHandle :: MonadIO m => Handle -> ConduitT Text o m ()
Documentation
A Mapper
consists of a decoder, an encoder, and a stream that transforms
each input into a (key, value)
pair.
A Reducer
consists of a decoder, an encoder, and a stream that transforms
each key and all values associated with the key into zero or more res
.
Eq k => Reducer | |
|
:: MonadIO m | |
=> (Text -> e -> m ()) | A action to be executed for each input that cannot be decoded. The first parameter
is the input and the second parameter is the decoding error. One may choose to, for instance,
increment a counter and |
-> Mapper e m | |
-> m () |
Run a Mapper
. Takes input from stdin
and emits the result to stdout
.
runMapper = runMapperWith (sourceHandle stdin) (sinkHandle stdout)
runMapperWith :: MonadIO m => ConduitT () Text m () -> ConduitT Text Void m () -> (Text -> e -> m ()) -> Mapper e m -> m () Source #
Like runMapper
, but allows specifying a source and a sink.
runMapper = runMapperWith (sourceHandle stdin) (sinkHandle stdout)
:: MonadIO m | |
=> (Text -> e -> m ()) | A action to be executed for each input that cannot be decoded. The first parameter
is the input and the second parameter is the decoding error. One may choose to, for instance,
increment a counter and |
-> Reducer e m | |
-> m () |
Run a Reducer
. Takes input from stdin
and emits the result to stdout
.
runReducer = runReducerWith (sourceHandle stdin) (sinkHandle stdout)
runReducerWith :: MonadIO m => ConduitT () Text m () -> ConduitT Text Void m () -> (Text -> e -> m ()) -> Reducer e m -> m () Source #
Like runReducer
, but allows specifying a source and a sink.
runReducer = runReducerWith (sourceHandle stdin) (sinkHandle stdout)
:: MonadIO m | |
=> Text | Group name. Must not contain comma. |
-> Text | Counter name. Must not contain comma. |
-> m () |
Increment a counter by 1.
:: MonadIO m | |
=> Int | |
-> Text | Group name. Must not contain comma. |
-> Text | Counter name. Must not contain comma. |
-> m () |
Increment a counter by n
.