Re: [Haskell-cafe] error vs. MonadError vs. fail

2006-03-28 Thread Daniel McAllansmith
On Tuesday 28 March 2006 07:29, Andrew Pimlott wrote:
  MonadError is not up to this task as far as I can tell.

 Why not?  All that needs to be done is write the missing instances, eg

 instance MonadError () Maybe where
   throwError x   = Nothing
   Nothing `catchError` f = f ()
   Just x `catchError` f  = Just x

 instance Error () where
   noMsg  = ()
   strMsg s   = ()


How would you go about writing the Maybe based analogue of ErrorT?  What do 
you give to the handler in the instance of MonadError?


newtype ErrMaybeT e m a = ErrMaybeT { runErrMaybeT :: m (Maybe a) }

instance (Monad m, Error e) = Monad (ErrMaybeT e m) where
return a = ErrMaybeT $ return (Just a)
m = k  = ErrMaybeT $ do
a - runErrMaybeT m
case a of
Nothing - return Nothing
Just r - runErrMaybeT (k r)
fail msg = ErrMaybeT $ return Nothing

instance (Monad m, Error e) = MonadError e (ErrMaybeT e m) where
throwError l = ErrMaybeT $ return Nothing
m `catchError` h = ErrMaybeT $ do
a - runErrMaybeT m
case a of
Nothing - runErrMaybeT (h ???) --what to do here?
Just r - return (Just r)

f :: (MonadError String m) = Bool - m Int
f b = if b
then return 42
else throwError The boolean was false.

test1 b = do
r - runErrorT $ f b
putStrLn (show r) --Left ... or Right 42
return ()

test2 b = do
r - runErrMaybeT $ f b
putStrLn (show r) --Nothing or Just 42
return ()


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


Re: [Haskell-cafe] error vs. MonadError vs. fail

2006-03-28 Thread Andrew Pimlott
On Wed, Mar 29, 2006 at 08:57:00AM +1200, Daniel McAllansmith wrote:
 On Tuesday 28 March 2006 07:29, Andrew Pimlott wrote:
   MonadError is not up to this task as far as I can tell.
 
  Why not?  All that needs to be done is write the missing instances, eg
 
  instance MonadError () Maybe where
throwError x   = Nothing
Nothing `catchError` f = f ()
Just x `catchError` f  = Just x
 
  instance Error () where
noMsg  = ()
strMsg s   = ()
 
 
 How would you go about writing the Maybe based analogue of ErrorT?

Maybe is a MonadError only with a dummy error type, which is why I used
() above.  Same with your ErrMaybeT:

newtype ErrMaybeT m a = ErrMaybeT { runErrMaybeT :: m (Maybe a) } 

instance Monad m = MonadError () (ErrMaybeT m) where
throwError l = ErrMaybeT $ return Nothing
m `catchError` h = ErrMaybeT $ do
a - runErrMaybeT m 
case a of
Nothing - runErrMaybeT (h ())
Just r - return (Just r)

If you want to write a MonadError operation that can be used with Maybe
or Either, it would look like

f :: (MonadError e m, Error e) = Bool - m Int 
f b = if b
then return 42
else throwError (strMsg The boolean was false.)

But I see your point now about MonadFail (having throw but not catch)
being perhaps preferable for this use.

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


Re: [Haskell-cafe] error vs. MonadError vs. fail

2006-03-28 Thread Daniel McAllansmith
On Wednesday 29 March 2006 09:49, Andrew Pimlott wrote:
 If you want to write a MonadError operation that can be used with Maybe
 or Either, it would look like

 f :: (MonadError e m, Error e) = Bool - m Int
 f b = if b
 then return 42
 else throwError (strMsg The boolean was false.)

As long as you're happy only using Strings for your error constructs.
Or you're willing to write a global construct-String codec across all error 
constructs.  Doesn't sound very pleasant to me.


 But I see your point now about MonadFail (having throw but not catch)
 being perhaps preferable for this use.

My intuition is that you'd want three error related monads, Fail, Catch and 
Convert, to achieve what I'm after... don't know if that's a good intuition 
or not. :)

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


Re: [Haskell-cafe] error vs. MonadError vs. fail

2006-03-27 Thread Andrew Pimlott
On Mon, Mar 27, 2006 at 02:53:58PM +1200, Daniel McAllansmith wrote:
 Is there a consensus on how anticipatable failure situations should be 
 handled?
 
 There was a thread, haskell programming guidelines, from 2006-02-25 where 
 John Meacham and Cale Gibbard had a bit of back-and-forth about using 
 Monad.fail or a purpose specific MonadFail class.
 
 Using fail certainly seems quick and easy, but I find it a bit
 distasteful for a few different reasons:

All of your reasons are good, but I recently tripped over an even better
one:  While fail must be defined in all monads, it has no sensible
definition in many, and so throws an exception.  I got burned because I
wrote a function to run some monad of mine, which might result in an
answer or an error, and I used fail for the error case:

run :: Monad m = MyMonad a - m a
run m = ... if ... then return x else fail e

Then, I accidentally (this was spread across two functions) ran my monad
twice:

run (run m)

This typechecked and crashed.  The inner run was given type

MyMonad a - MyMonad a

and you can guess what fail does in MyMonad.  Ugh.  If I had used
MonadError for the return value of run, run would only typecheck in a
monad that can sensibly handle errors, catching my bug.

 Apparently the advantage of fail is that user of the library can choose to 
 receive failures as eg Maybes, Eithers, [], or whatever they like.
...
 MonadError is not up to this task as far as I can tell.

Why not?  All that needs to be done is write the missing instances, eg

instance MonadError () Maybe where
  throwError x   = Nothing
  Nothing `catchError` f = f ()
  Just x `catchError` f  = Just x

instance Error () where
  noMsg  = ()
  strMsg s   = () 

As you might tell, I would like to see this instance in MonadError.  An
instance for [] is however questionable, IMO.

BTW, I've posted about these issues several times, eg

http://www.haskell.org/pipermail/haskell-cafe/2005-June/010361.html

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


[Haskell-cafe] error vs. MonadError vs. fail

2006-03-26 Thread Daniel McAllansmith
Is there a consensus on how anticipatable failure situations should be 
handled?


There was a thread, haskell programming guidelines, from 2006-02-25 where 
John Meacham and Cale Gibbard had a bit of back-and-forth about using 
Monad.fail or a purpose specific MonadFail class.

I believe a consensus was reached that using error should only be for 
'impossible' situations and signaling buggy code.
[Apologies if I've put words in anyones mouth.]


Using fail certainly seems quick and easy, but I find it a bit distasteful for 
a few different reasons:
 users of a library can't discriminate between a failure indicating they've 
supplied bad input and a failure indicating that teh library writer has got a 
bad pattern match somewhere,
 it doesn't seem to force the potential for failure to be explicit in the api 
of a library,
 it doesn't seem to allow distinct, and rich, failure constructs at system 
layer boundaries, or the containment of them.

Maybe the last two aren't a problem when programming in Haskell, but by itself 
the first seems pretty nasty.


Apparently the advantage of fail is that user of the library can choose to 
receive failures as eg Maybes, Eithers, [], or whatever they like.

But surely a MonadFail could allow the best of both worlds, letting the 
library throw as detailed an error construct as it can, and letting the 
library user choose MonadFail instance such that error constructs are turned 
into Maybes, Eithers, a new construct appropriate for a higher system layer, 
etc?


MonadError is not up to this task as far as I can tell.  Has anybody whipped 
up an alternative, or can explain why it can't be done?


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