#4159: move Monad and MonadFix instances for Either from mtl to base

Claus Reinke claus.reinke at talk21.com
Wed Jun 30 18:29:57 EDT 2010


>> Note that my opposition is against making 'Monad (Either a)' less
>> defined and less tunable than it is at the moment.
>
> It's a common trade-off: the Error constraint limits the instances that
> are available, but gives you a bit more when you have an instance.  One
> must weigh the relative value of fail vs the unconstrained instance.

If there is no full definition of 'Monad (Either a)' for all 'a', then
qualifying 'a' by an additional type class seems to be the standard
Haskell solution. As I said, even if you just want to drop 'Error', you
could define 'fail s = Left (error s)'. That would still be less defined
than the current instance, but more defined than the proposed
instance. So you've deliberately chosen not to use 'Left' and not
to represent 'fail' in the data type.

>> If you are just concerned about the Error constraint, simply provide
>> a default instance that maps strMsg to error (see example of default
>> instances with user override in base Data.Typable). That way, you'd
>> get 'Monad (Either a)' without Error constraint, but with strictly more
>> defined fail ('Left _|_' instead of '_|_'), and others can add even more
>> defined fail when needed.
>
> Do you mean an overlapping instance?  There are problems with that too.

Yes to both. But it would avoid the problems with the unconstrained
Monad instance for Either a, wouldn't it? And most of the time, neither
the OverlappingInstances nor the Error constraint would be visible
to client code, while the 'fail = error' default would be quite visible
(with your instance version, none of the Either lines in client.hs
below would return any information before throwing the error).

Claus

----------------------- Lib.hs
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
module Lib where
import Control.Monad

class Error a where strMsg :: String -> a

instance Error String where strMsg = id
instance Error a      where strMsg = error

instance Error a => Monad (Either a) where
  Left l  >>= _ = Left l
  Right r >>= f = f r

  return = Right
  fail   = Left . strMsg

instance Error a => MonadPlus (Either a) where
  mzero = Left (strMsg "mzero")
  Left _  `mplus` x = x
  Right r `mplus` _ = Right r

--------------------client.hs
import Lib
import Control.Monad

x,y,z :: MonadPlus m => m Int
x = do 1 <- return 2; return 21
y = do 2 <- return 2; return 42
z = x `mplus` y

main = do
  print (z::Maybe Int)
  print (x::Maybe Int)
  print (z::[Int])
  print (x::[Int])
  print (z::Either String Int)
  print (z::Either Bool Int)
  print (x::Either String Int)
  print (x::Either Bool Int)

----------------- output
*Main> main
Just 42
Nothing
[42]
[]
Right 42
Right 42
Left "Pattern match failure in do expression at .. client.hs:5:7"
Left *** Exception: Pattern match failure in do expression at .. 
client.hs:5:7

 




More information about the Libraries mailing list