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.ji...@gmail.com




_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to