hslogstash-0.4.2: A library to work with, or as, a logstash server

Safe HaskellNone
LanguageHaskell2010

Data.Conduit.Branching

Description

WARNING: executables using this function must be compiled with -threaded

These functions let you connect several sinks to a single source, according to a branching strategy. For example :

module Main where

import Data.Conduit.Branching
import Data.Conduit
import qualified Data.Conduit.List as CL
import Control.Monad.IO.Class

src :: Monad m => Producer m (Either Int String)
src = CL.sourceList [Left 5, Left 4, Right "five", Right "four"]

sinkString :: (Monad m, MonadIO m) => Sink (Either Int String) m ()
sinkString = CL.mapM_ $ (Right x) -> liftIO (putStrLn ("This is a string: " ++ x))

sinkInt :: (Monad m, MonadIO m) => Sink (Either Int String) m ()
sinkInt = CL.mapM_ $ (Left x) -> liftIO (putStrLn ("This is an integer: " ++ show x))

sinkLog :: (Monad m, MonadIO m) => Sink (Either Int String) m ()
sinkLog = CL.mapM_ (liftIO . putStrLn . ("Raw logging: " ++) . show)

main :: IO ()
main = branchConduits src branching [sinkInt, sinkString, sinkLog]
    where
        branching (Left _) = [0,2]
        branching (Right _) = [1,2]

Synopsis

Documentation

mkBranchingConduit Source

Arguments

:: MonadResource m 
=> Int

Number of branches

-> (a -> [Int])

Branching function, where 0 is the first branch

-> IO (Sink a m (), [Source m a])

Returns a sink and N sources

Creates the plumbing that might be used to connect several conduits together, based on a branching function.

branchConduits Source

Arguments

:: Source (ResourceT IO) a

The source to branch from

-> (a -> [Int])

The branching function (0 is the first sink)

-> [Sink a (ResourceT IO) ()]

The destination sinks

-> IO ()

Results of the sinks

A higher level function. Given a source, a branching function and a list of sinks, this will run the conduits until completion.