I'm looking to make a function with the following signature (I think):
partialProcessConduit :: forall m a b r. Monad m
=> (a -> (b, Maybe (ConduitT () a m ()) ))
-> ConduitT b Void m r
-> ConduitT () a m ()
-> m (r, ConduitT () a m ())
partialProcessConduit splitFunc consumingConduit sourceConduit
Which basically does the following:
- Repeatedly gets a value of type
aout of the the conduitsourceConduit. - Applies the functions
splitFuncto that valuea. - Pushes the value
bfromsplitFuncintoconsumingConduit - IF
splitFuncreturnsJust (some conduit)(i.e. notNothing) for the second part of it's returned pair THEN- "close up"
consumingConduit, and get the result valuer - Return a conduit with the "rest" of
sourceConduit, but with conduit in the Just appended in front of it.
- "close up"
I've actually achieved something close to this (apologies in advance for crappy naming). See here:
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Conduit (ConduitT, SealedConduitT, unsealConduitT, ($$+), await)
import Data.Void (Void)
import qualified Control.Arrow as Arrow
import Data.DList (DList)
partialProcessConduitInMemory :: forall m a b r. Monad m
=> (a -> (b, Maybe (ConduitT () a m ())))
-> (DList b -> r)
-> ConduitT () a m ()
-> m (r, ConduitT () a m ())
partialProcessConduitInMemory splitFunc collapseDList sourceConduit = do
(sc :: SealedConduitT () a m (), (result :: r, leftOver :: ConduitT () a m ())) <- x
pure (result, leftOver >> unsealConduitT sc)
where
x :: m (SealedConduitT () a m (), (r, ConduitT () a m ()))
x = sourceConduit $$+ g
g :: ConduitT a Void m (r, ConduitT () a m ())
g = Arrow.first collapseDList <$> go mempty
go :: DList b -> ConduitT a Void m (DList b, ConduitT () a m ())
go blockList = await >>= \case
Nothing -> pure (blockList, pure ())
Just block -> case splitFunc block of
(transformedBlock, Nothing) -> go $ blockList <> pure transformedBlock
(transformedBlock, Just leftOver) -> pure (blockList <> pure transformedBlock, leftOver)
This is almost what I want. Notice the type signature here is the same as above EXCEPT for the second argument. Here, instead of passing a conduit sink that consumes the elements as the second argument, I'm collecting them in a `DList. I'd rather be able to use a conduit sink to consume the first part of the conduit source, instead of collecting all the elements in a list and processing them.
Am I able to use a conduit sink here instead of the DList, and if so, what sort of adjustments do I need to make? I thought about pushing elements into the sink in the go loop instead of just appending them, and then doing runConduit to get the result r somehow, but I wasn't able to play nice with the types. Any help appreciated.
I suppose you want something like this:
The
loopconduit here has typeConduitT a b m (Maybe (ConduitT () a m ()), so it inputsas and outputsbs untilf(AKAsplitFunc) returns a prefix conduit, in which case it returnsJustthat conduit. IfsplitFuncnever returns a conduit, it returnsNothing.Now, we can
fuseBoth loop snk, which has typeConduitT a Void m (Maybe (ConduitT () a m (), r). This sinks thebs fromloopinto thesnk, returning both the prefix conduit fromsplitFunc, if any, and the returnrfromsnk.Finally, we can
src $$+ fuseBoth loop snk. This will run the whole conduit sourcingas fromsrcand sinkingbs intosnk, untilsplitFuncreturns a prefix conduit, at which point it will return:where, incredibly, the sealed conduit is what's left of
src, theMaybeconduit is the "prefix" conduit returned bysplitFunc, and the finalris the return value fromsnk. All that's left is to glue this together into an appropriate return value.This seems to work as per the following test:
This outputs:
which looks right.