hw-conduit-merges-0.2.0.0: Additional merges and joins for Conduit

Safe HaskellNone
LanguageHaskell2010

HaskellWorks.Data.Conduit.Merge

Synopsis

Documentation

data JoinResult a v b Source #

A result value of joining two sources.

When sources are joined, the result value can be a value or it be a leftover on either left or right side in case if one of the streams is ehausted before another.

Constructors

LeftoverL a

Leftover on the left side, the right side is exhausted

JoinValue v

Result value

LeftoverR b

Leftover on the right side, the left side is exhausted

Instances
(Eq a, Eq v, Eq b) => Eq (JoinResult a v b) Source # 
Instance details

Defined in HaskellWorks.Data.Conduit.Merge

Methods

(==) :: JoinResult a v b -> JoinResult a v b -> Bool #

(/=) :: JoinResult a v b -> JoinResult a v b -> Bool #

(Show a, Show v, Show b) => Show (JoinResult a v b) Source # 
Instance details

Defined in HaskellWorks.Data.Conduit.Merge

Methods

showsPrec :: Int -> JoinResult a v b -> ShowS #

show :: JoinResult a v b -> String #

showList :: [JoinResult a v b] -> ShowS #

joinSources Source #

Arguments

:: Monad m 
=> (a -> b -> ([a], [v], [b]))

Function to merge values. The result contains values v and possible leftovers a and b for left and right streams.

-> ConduitT () a m ()

Left side source

-> ConduitT () b m ()

Right side source

-> ConduitT () (JoinResult a v b) m ()

Result source that can contain a value or leftovers on each side

Joins sources with the provided merging function. Leftovers are considered valid values and are retuned as a part of a result stream.

  import Data.Conduit
  import Data.Conduit.List as CL

  -- combining function just sums both values
  comb :: (Ord a, Num a) => a -> a -> ([a], [a], [a])
  comb a b
    | a > b     = ([a - b], [b], [])
    | b > a     = ([], [a], [b - a])
    | otherwise = ([], [a], [])

  let lst1 = CL.sourceList [1,2,3]
  let lst2 = CL.sourceList [1,2,3,4,5]
  runConduit $ joinSources comb lst1 lst2 $$ CL.take 1000

  [JoinValue 2,JoinValue 4,JoinValue 6,LeftoverR 4,LeftoverR 5]

joinResumableSources Source #

Arguments

:: Monad m 
=> (a -> b -> ([a], [v], [b]))

Function to merge values. The result contains values v and possible leftovers a and b for left and right streams.

-> SealedConduitT () a m ()

Left side source

-> SealedConduitT () b m ()

Right side source

-> ConduitT () (JoinResult a v b) m ()

Result source that can contain a value or leftovers on each side