How to handle exceptions in conduit?

Hi, there I'm writing a program communicating with external process, which can be sometimes fail, using conduit and process-conduit package. Consider the following example, which reads paths from the config file, and passes their contents to external process, and output the results: ```exc.hs module Main where import qualified Data.ByteString.Char8 as BS import Data.Conduit import qualified Data.Conduit.Binary as BC import qualified Data.Conduit.List as LC import Data.Conduit.Process main :: IO () main = runResourceT $ BC.sourceFile "paths.dat" $$ BC.lines =$= myConduit =$= LC.mapM_ (unsafeLiftIO . BS.putStrLn) myConduit :: MonadResource m => Conduit BS.ByteString m BS.ByteString myConduit = awaitForever $ \path -> BC.sourceFile (BS.unpack path) =$= conduitCmd "./sometimes-fail" ``` ```sometimes-fail.hs module Main where import System.Random main :: IO () main = do b <- randomRIO (1,10 :: Int) if b < 9 then interact id else error "error!" ``` ```paths.dat txt/a.dat txt/b.dat txt/c.dat ...bra, bra, bra... ``` As you can see, `sometimes-fail` is a simple echoing program, but sometimes fail at random. Successful result is below: ``` $ ./exc this is a! this is b! this is c! this was d! this was e! and this is f. ``` but if `sometimes-fail` fails in some place, `exc` exits with exception like below: ``` $ ./exc this is a! this is b! this is c! sometimes-fail: error! ``` But I want to write the program acts like below: ``` $ ./exc this is a! this is b! this is c! sometimes-fail: error! this was e! and this is f. ``` that is, ignore the exception and continue to process remaining streams. So, the question is: how to handle the exception in `myConduit` and proceed to remaining works? In `conduit` package, `Pipe` type is not an instance of `MonadBaseControl IO` so it cannot handle exceptions within it. I think this is necessary to make `ResourceT` release resources correctly. So, how to write the Conduit that ignores some kind of exceptions and proceed to remaining works? One sometimes want to ignore the invalid input and/or output and just continue to process the remaining stream. One solution is that libraries using conduit provide "failure-ignore" version for all the `Pipe`s included in the library, but I think it is too heavy solution. It is ideal that `conduit` can package provides combinator that makes exsiting `Pipe`s "failure-ignore". -- Hiromi ISHII konn.jinro@gmail.com

Due to various technical reasons regarding the nature of conduit, you can't
currently catch exceptions within the Pipe monad. You have two options:
* Catch exceptions before `lift`ing.
* Catch exceptions thrown from the entire Pipe.
Since the exceptions are always originating in the underlying monad, the
first choice is certainly possible in theory, though may require reworking
the library you're using a bit.
One other possibility that I haven't actually tried would be to use
transPipe[1] to catch all of the exceptions, though I'm not sure how well
that would work in practice.
If people have ideas on how to improve the exception handling facilities of
conduit, please let me know.
Michael
[1]
http://hackage.haskell.org/packages/archive/conduit/0.5.2.7/doc/html/Data-Co...
On Thu, Nov 1, 2012 at 6:26 AM, Hiromi ISHII
Hi, there
I'm writing a program communicating with external process, which can be sometimes fail, using conduit and process-conduit package.
Consider the following example, which reads paths from the config file, and passes their contents to external process, and output the results:
```exc.hs module Main where import qualified Data.ByteString.Char8 as BS import Data.Conduit import qualified Data.Conduit.Binary as BC import qualified Data.Conduit.List as LC import Data.Conduit.Process
main :: IO () main = runResourceT $ BC.sourceFile "paths.dat" $$ BC.lines =$= myConduit =$= LC.mapM_ (unsafeLiftIO . BS.putStrLn)
myConduit :: MonadResource m => Conduit BS.ByteString m BS.ByteString myConduit = awaitForever $ \path -> BC.sourceFile (BS.unpack path) =$= conduitCmd "./sometimes-fail" ```
```sometimes-fail.hs module Main where import System.Random
main :: IO () main = do b <- randomRIO (1,10 :: Int) if b < 9 then interact id else error "error!" ```
```paths.dat txt/a.dat txt/b.dat txt/c.dat ...bra, bra, bra... ```
As you can see, `sometimes-fail` is a simple echoing program, but sometimes fail at random.
Successful result is below:
``` $ ./exc this is a!
this is b!
this is c!
this was d!
this was e!
and this is f. ```
but if `sometimes-fail` fails in some place, `exc` exits with exception like below:
``` $ ./exc this is a!
this is b!
this is c! sometimes-fail: error! ```
But I want to write the program acts like below:
``` $ ./exc this is a!
this is b!
this is c! sometimes-fail: error! this was e!
and this is f. ```
that is, ignore the exception and continue to process remaining streams.
So, the question is: how to handle the exception in `myConduit` and proceed to remaining works?
In `conduit` package, `Pipe` type is not an instance of `MonadBaseControl IO` so it cannot handle exceptions within it. I think this is necessary to make `ResourceT` release resources correctly.
So, how to write the Conduit that ignores some kind of exceptions and proceed to remaining works? One sometimes want to ignore the invalid input and/or output and just continue to process the remaining stream.
One solution is that libraries using conduit provide "failure-ignore" version for all the `Pipe`s included in the library, but I think it is too heavy solution. It is ideal that `conduit` can package provides combinator that makes exsiting `Pipe`s "failure-ignore".
-- Hiromi ISHII konn.jinro@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, there On 2012/11/01, at 21:23, Michael Snoyman wrote:
Due to various technical reasons regarding the nature of conduit, you can't currently catch exceptions within the Pipe monad. You have two options:
* Catch exceptions before `lift`ing. * Catch exceptions thrown from the entire Pipe.
Since the exceptions are always originating in the underlying monad, the first choice is certainly possible in theory, though may require reworking the library you're using a bit.
Thanks. In my case, used library is relatively small so I can rewrite it to ignore exception before lifting. But I think it is more convenient doing the same thing without modifying existing code. The second choice does not match my case because it cannot resume the process from the place just after an exception occurred.
One other possibility that I haven't actually tried would be to use transPipe[1] to catch all of the exceptions, though I'm not sure how well that would work in practice.
The type of the first argument of `transPipe` should be general, so I think we can't compose it with `catch` function. -- Hiromi ISHII konn.jinro@gmail.com

On Nov 5, 2012 2:42 PM, "Hiromi ISHII"
Hi, there
On 2012/11/01, at 21:23, Michael Snoyman wrote:
Due to various technical reasons regarding the nature of conduit, you
* Catch exceptions before `lift`ing. * Catch exceptions thrown from the entire Pipe.
Since the exceptions are always originating in the underlying monad,
can't currently catch exceptions within the Pipe monad. You have two options: the first choice is certainly possible in theory, though may require reworking the library you're using a bit.
Thanks. In my case, used library is relatively small so I can rewrite it
But I think it is more convenient doing the same thing without modifying existing code.
The second choice does not match my case because it cannot resume the
One other possibility that I haven't actually tried would be to use
to ignore exception before lifting. process from the place just after an exception occurred. I agree that it would be great if conduit could meet your use case better. I haven't spent enough cycles looking at this yet to determine if the reason we don't have this support is a limitation in the conduit approach itself, or just a limitation in what I was able to implement so far. If you can think of a way to implement more fine-grained exception handling (or anyone else for that matter), I'd love to hear about it. transPipe[1] to catch all of the exceptions, though I'm not sure how well that would work in practice.
The type of the first argument of `transPipe` should be general, so I
think we can't compose it with `catch` function. That makes sense.
-- Hiromi ISHII konn.jinro@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Nov 5, 2012 at 9:51 PM, Michael Snoyman
On Nov 5, 2012 2:42 PM, "Hiromi ISHII"
wrote: Hi, there
On 2012/11/01, at 21:23, Michael Snoyman wrote:
Due to various technical reasons regarding the nature of conduit, you
* Catch exceptions before `lift`ing. * Catch exceptions thrown from the entire Pipe.
Since the exceptions are always originating in the underlying monad,
can't currently catch exceptions within the Pipe monad. You have two options: the first choice is certainly possible in theory, though may require reworking the library you're using a bit.
Thanks. In my case, used library is relatively small so I can rewrite it
But I think it is more convenient doing the same thing without modifying existing code.
The second choice does not match my case because it cannot resume the
to ignore exception before lifting. process from the place just after an exception occurred.
I agree that it would be great if conduit could meet your use case better. I haven't spent enough cycles looking at this yet to determine if the reason we don't have this support is a limitation in the conduit approach itself, or just a limitation in what I was able to implement so far. If you can think of a way to implement more fine-grained exception handling (or anyone else for that matter), I'd love to hear about it.
One other possibility that I haven't actually tried would be to use transPipe[1] to catch all of the exceptions, though I'm not sure how well that would work in practice.
The type of the first argument of `transPipe` should be general, so I think we can't compose it with `catch` function.
That makes sense.
-- Hiromi ISHII konn.jinro@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Sorry, small follow-up. It's certainly possible to make some kind of
catching function, e.g.: catchPipe :: (MonadBaseControl IO m, Exception e) => Pipe l i o u m r -> (e -> Pipe l i o u m r) -> Pipe l i o u m r catchPipe (HaveOutput p c o) f = HaveOutput (catchPipe p f) c o catchPipe (NeedInput p c) f = NeedInput (flip catchPipe f . p) (flip catchPipe f . c) catchPipe (Done r) _ = Done r catchPipe (PipeM mp) f = PipeM $ Control.Exception.Lifted.catch (liftM (flip catchPipe f) mp) (return . f) catchPipe (Leftover p l) f = Leftover (catchPipe p f) l I'm just not certain how useful this is in practice, as it doesn't really give you any information on what else that Pipe was about to perform. So you can't really just pick up where you left off. Michael
participants (2)
-
Hiromi ISHII
-
Michael Snoyman