Re: [Haskell-cafe] How to handle exceptions in conduit?

2012-11-05 Thread 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 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.ji...@gmail.com




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


[Haskell-cafe] How to handle exceptions in conduit?

2012-10-31 Thread 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.ji...@gmail.com




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


Re: [Haskell-cafe] How to write Source for TChan working with LC.take?

2012-05-30 Thread Hiromi ISHII
Thanks!

I just read your article. I think your proposal is rational, useful and so 
brilliant!
The new yield/await style would make writing conduits much easier.

Thank you again for taking so much time for this problem!

On 2012/05/29, at 22:14, Michael Snoyman wrote:

 OK, after thinking on this for the past week, I've come up with a
 proposal to make this kind of code easier to write (and more of an
 explanation on why the behavior was unintuitive in the first place).
 
 http://www.yesodweb.com/blog/2012/05/next-conduit-changes
 
 Do you think the modified yield/await would be a good solution to the problem?
 
 Michael
 
 On Mon, May 21, 2012 at 6:07 AM, Michael Snoyman mich...@snoyman.com wrote:
 I agree that this behavior is non-intuitive, but still believe it's
 the necessary approach. The short answer to why it's happening is that
 there's no exit path in the yield version of the function. To
 understand why, let's expand the code a little bit. Realizing that
 
liftIO = lift . liftIO
 
 and
 
lift mr = PipeM (Done Nothing `liftM` mr) (Finalize mr)
 
 we can expand the yield version into:
 
 sourceTChanYield2 ch = forever $ do
  let action = liftIO . atomically $ readTChan ch
  ans - PipeM (Done Nothing `liftM` action) (FinalizeM action)
  yield ans
 
 So the first hint that something is wrong is that the finalize
 function is calling the action. If you try to change that finalize
 action into a no-op, e.g.:
 
 sourceTChanYield3 :: MonadIO m = TChan a - Source m a
 sourceTChanYield3 ch = forever $ do
  let action = liftIO . atomically $ readTChan ch
  ans - PipeM (Done Nothing `liftM` action) (return ())
  yield ans
 
 then you get an error message:
 
 test.hs:36:53:
Could not deduce (a ~ ())
 
 The problem is that, as the monadic binding is set up here, the code
 says after running the PipeM, I want you to continue by yielding, and
 then start over again. If you want to expand it further, you can
 change `forever` into a recursive call, expand `yield`, and then
 expand all the monadic binding. Every finalization call is forcing
 things to keep running.
 
 And remember: all of this is the desired behavior of conduit, since we
 want to guarantee finalizers are always called. Imagine that, instead
 of reading data from a TChan, you were reading from a Handle. In the
 code above, there was no way to call out to the finalizers.
 
 Not sure if all of that rambling was coherent, but here's my
 recommended solution. What we need is a helper function that allows
 you to branch based on whether or not it's time to clean up. `lift`,
 `liftIO`, and monadic bind all perform the same actions regardless of
 whether or not finalization is being called. The following code,
 however, works correctly:
 
 liftFinal :: Monad m = m a - Finalize m () - (a - Source m a) - Source 
 m a
 liftFinal action final f = PipeM (liftM f action) final
 
 sourceTChanYield :: Show a = MonadIO m = TChan a - Source m a
 sourceTChanYield ch = liftFinal
(liftIO . atomically $ readTChan ch)
(return ())
$ \ans - do
yield ans
sourceTChanYield ch
 
 Michael
 
 On Sun, May 20, 2012 at 4:22 PM, Hiromi ISHII konn.ji...@gmail.com wrote:
 Oops, sorry.
 The last case's behaviour was not as I expected... A correct log is below:
 
 
 ghci sourceTChanRaw ch $$ LC.isolate 10 =$= LC.mapM_ print
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ghci sourceTChanState ch $$ LC.isolate 10 =$= LC.mapM_ print
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ghci sourceTChanYield ch $$ LC.isolate 10 =$= LC.mapM_ print
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 *blocks*
 
 
 So again, sourceTChanYield blocks here even if it is already supplied with 
 enough values!
 
 -- Hiromi ISHII
 konn.ji...@gmail.com
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

-- Hiromi ISHII
konn.ji...@gmail.com




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


[Haskell-cafe] How to write Source for TChan working with LC.take?

2012-05-20 Thread Hiromi ISHII
Hello, there.

I'm writing a Source to supply values from TChan.
I wrote three implementations for that goal as follows:


import Data.Conduit
import qualified Data.Conduit.List as LC
import Control.Monad.Trans
import Control.Concurrent.STM
import Control.Monad

sourceTChanRaw :: MonadIO m = TChan a - Source m a
sourceTChanRaw ch = pipe
  where
pipe = PipeM next (return ())
next = do
  o - liftIO $ atomically $ readTChan ch
  return $ HaveOutput pipe (return ()) o

sourceTChanState :: MonadIO m = TChan a - Source m a
sourceTChanState ch = sourceState ch puller
  where
puller ch = StateOpen ch `liftM` (liftIO . atomically $ readTChan ch)

sourceTChanYield :: MonadIO m = TChan a - Source m a
sourceTChanYield ch = forever $ do
  ans - liftIO . atomically $ readTChan ch
  yield ans


Namely, one using raw Pipe constructors directly, using `sourceState` and 
`yield`.
I tested these with GHCi.


ghci ch - newTChanIO :: IO (TChan ())
ghci atomically $ replicateM_ 1500 $ writeTChan ch ()
ghci sourceTChanRaw ch $$ LC.take 10
[(),(),(),(),(),(),(),(),(),()]
ghci sourceTChanState ch $$ LC.take 10
[(),(),(),(),(),(),(),(),(),()]
ghci sourceTChanYield ch $$ LC.take 10
*thread blocks*


First two versions' result is what I exactly expected but the last one not: the 
source written with `yield` never returns value even if there are much enough 
value.

I also realized that following code runs perfectly as I expected:


ghci ch - newTChanIO :: IO (TChan ())
ghci atomically $ replicateM_ 1500 $ writeTChan ch ()
ghci sourceTChanRaw ch $= LC.isolate 10 $$ LC.mapM_ print
[(),(),(),(),(),(),(),(),(),()]
ghci sourceTChanState ch $= LC.isolate 10 $$ LC.mapM_ print
[(),(),(),(),(),(),(),(),(),()]
ghci sourceTChanYield ch $= LC.isolate 10 $$ LC.mapM_ print
[(),(),(),(),(),(),(),(),(),()]


So, here is the question:

Why the Source using `yield` doesn't work as expected with LC.take?

Or, might be

Semantically, what behaviour should be expected for LC.take?


Thanks,

-- Hiromi ISHII
konn.ji...@gmail.com




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


Re: [Haskell-cafe] How to write Source for TChan working with LC.take?

2012-05-20 Thread Hiromi ISHII
Oops, sorry.
The last case's behaviour was not as I expected... A correct log is below:


ghci sourceTChanRaw ch $$ LC.isolate 10 =$= LC.mapM_ print
()
()
()
()
()
()
()
()
()
()
ghci sourceTChanState ch $$ LC.isolate 10 =$= LC.mapM_ print
()
()
()
()
()
()
()
()
()
()
ghci sourceTChanYield ch $$ LC.isolate 10 =$= LC.mapM_ print
()
()
()
()
()
()
()
()
()
()
*blocks*


So again, sourceTChanYield blocks here even if it is already supplied with 
enough values! 

-- Hiromi ISHII
konn.ji...@gmail.com




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