Hi,

Isn't it by design? Consider the next code:


import Data.Enumerator (($$), (>>==))
import qualified Data.Enumerator as E
import qualified Data.Enumerator.List as EL
import Control.Exception
import Control.Monad.IO.Class

main :: IO ()
main = do
  res <- E.run $ myEnum $$
    EL.take 5 `E.catchError` (\_ -> liftIO (print "exception") >> return
[])
  print res

myEnum :: Monad m => E.Enumerator Int m b
-- myEnum (E.Continue k) = k (E.Chunks [1, 2]) >>== myEnum  -- (1)
-- myEnum (E.Continue k) = E.throwError (ErrorCall "EEE")   -- (2)
myEnum step = E.returnI step


If uncomment (1), then myEnum will generate infinite list like [1, 2, 1,
2, ...]. If uncomment (2), then it will throw exception, and it can't be
caught. Is it a correct behavior? Or I have a bug in "myEnum"
implementation?

It makes some sense for me: when enumerator throws error, then there is
no way to proceed, and "E.run" returns Left immediately. So,
"throwError" in enumerator can't be caught. Is it correct?

Then it seems to be a design bug in websockets -- it is not possible to
know from the WebSockets monad that client closed connection.

Thanks,
Yuras

On Thu, 2013-08-29 at 14:04 +0300, Yuras Shumovich wrote:
> Hi,
> 
> Thank you for the reply.
> 
> Unlikely it is the case (if I understand it correctly). The exception is
> thrown by "enumSocket", I added traces to prove that. And it is
> propagated to
> "runWithSocket" ( 
> http://hackage.haskell.org/packages/archive/websockets/0.7.4.0/doc/html/src/Network-WebSockets-Socket.html#runWithSocket
>  ), so that "Data.Enumerator.run" returns "Left". So actually it is not an IO 
> exception, but it is thrown via "throwError".
> 
> Looks like I don't have other options except to reimplement websockets
> protocol myself :(
> 
> Thanks,
> Yuras
> 
> On Tue, 2013-08-27 at 15:40 -0400, Ben Doyle wrote:
> > This is partially guesswork, but the code to catchWSError looks
> > dubious:
> > 
> > 
> >     catchWsError :: WebSockets p a
> >              -> (SomeException -> WebSockets p a)
> >              -> WebSockets p a
> >   catchWsError act c = WebSockets $ do
> >       env <- ask
> >       let it  = peelWebSockets env $ act
> >           cit = peelWebSockets env . c
> >       lift $ it `E.catchError` cit
> >     where
> >       peelWebSockets env = flip runReaderT env . unWebSockets
> > 
> > Look at `cit`. It runs the recovery function, then hands the underlying 
> > Iteratee the existing environment. That's fine if `act` is at fault, but 
> > there are Iteratee- and IO-ish things in WebSocketsEnv---if one of 
> > `envSink` or `envSendBuilder` is causing the exception, it'll just get 
> > re-thrown after `E.catchError`. (I think. That's the guesswork part.)
> > So check how `envSendBuilder` is built up, and see if there's a way it 
> > could throw an exception on client disconnect.
> > 
> > 
> > On Tue, Aug 27, 2013 at 10:28 AM, Yuras Shumovich
> > <shumovi...@gmail.com> wrote:
> >         Hello,
> >         
> >         I'm debugging an issue in "websockets" package,
> >         https://github.com/jaspervdj/websockets/issues/42
> >         
> >         I'm not familiar with "enumerator" package (websockets are
> >         based on it),
> >         so I'm looking for help. The exception is throws inside
> >         "enumSocket"
> >         enumerator using
> >         "throwError" ( 
> > http://hackage.haskell.org/packages/archive/network-enumerator/0.1.5/doc/html/src/Network-Socket-Enumerator.html#enumSocket
> >  ), but I can't catch it with "catchError". It is propagated to "run" 
> > function:
> >            <interactive>: recv: resource vanished (Connection reset by
> >         peer)
> >         
> >         The question is: how is it possible? could it be a bug in
> >         "enumerator"
> >         package?
> >         
> >         Thanks,
> >         Yuras
> >         
> >         
> >         _______________________________________________
> >         Haskell-Cafe mailing list
> >         Haskell-Cafe@haskell.org
> >         http://www.haskell.org/mailman/listinfo/haskell-cafe
> > 
> > 
> 
> 



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

Reply via email to