Why does the transformers/mtl 'Error' class exist?

Both the transformers[1] and mtl[2] define a class named 'Error', for use with MonadError and ErrorT. This class is required for the instance of Monad (and therefore MonadTrans, MonadIO, etc). However, I can't figure out why this class exists. Its presence means that instead of something like: ------------------------------------- data NameError = ErrorFoo | ErrorBar validateName :: Monad m => Text -> m (Either Error Text) validateName x = runErrorT $ do when (some condition) $ throwError ErrorFoo when (other condition) $ throwError ErrorBar return x ------------------------------------- I have to define this, which is more verbose, no more useful, and adds a "fake" class to the Haddock docs (with a warning not to use it): ------------------------------------- data Error = ErrorFoo | ErrorBar instance Error NameError where strMsg = error -- validateName ... ------------------------------------- Is there any good reason why the 'Error' class can't just be removed? [1] http://hackage.haskell.org/packages/archive/transformers/0.2.0.0/doc/html/Co... [2] http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Mon...

It's used in the implementation of "fail" for those monads.
class Monad m where
...
fail :: String -> m a
fail = error -- default implementation
which is then used to desugar do-notation when pattern matching fails:
do
Left x <- something
return x
=>
something >>= \v -> case v of { Left x -> return x ; _ -> fail
"Pattern match failure ..." }
You can argue about whether "fail" belongs in Monad (and many people
have), but that's why it is how it is.
-- ryan
On Thu, Apr 15, 2010 at 7:18 PM, John Millikin
Both the transformers[1] and mtl[2] define a class named 'Error', for use with MonadError and ErrorT. This class is required for the instance of Monad (and therefore MonadTrans, MonadIO, etc). However, I can't figure out why this class exists. Its presence means that instead of something like:
------------------------------------- data NameError = ErrorFoo | ErrorBar validateName :: Monad m => Text -> m (Either Error Text) validateName x = runErrorT $ do when (some condition) $ throwError ErrorFoo when (other condition) $ throwError ErrorBar return x -------------------------------------
I have to define this, which is more verbose, no more useful, and adds a "fake" class to the Haddock docs (with a warning not to use it): ------------------------------------- data Error = ErrorFoo | ErrorBar
instance Error NameError where strMsg = error
-- validateName ... -------------------------------------
Is there any good reason why the 'Error' class can't just be removed?
[1] http://hackage.haskell.org/packages/archive/transformers/0.2.0.0/doc/html/Co... [2] http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Mon... _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan Ingram schrieb:
It's used in the implementation of "fail" for those monads.
class Monad m where ... fail :: String -> m a fail = error -- default implementation
which is then used to desugar do-notation when pattern matching fails:
do Left x <- something return x => something >>= \v -> case v of { Left x -> return x ; _ -> fail "Pattern match failure ..." }
You can argue about whether "fail" belongs in Monad (and many people have), but that's why it is how it is.
I also prefered to not support the fail method in this way and wrote: http://hackage.haskell.org/packages/archive/explicit-exception/0.1.4/doc/htm...

On Sat, Apr 17, 2010 at 2:52 PM, Henning Thielemann
Ryan Ingram schrieb:
It's used in the implementation of "fail" for those monads.
class Monad m where ... fail :: String -> m a fail = error -- default implementation
which is then used to desugar do-notation when pattern matching fails:
do Left x <- something return x => something >>= \v -> case v of { Left x -> return x ; _ -> fail "Pattern match failure ..." }
You can argue about whether "fail" belongs in Monad (and many people have), but that's why it is how it is.
I also prefered to not support the fail method in this way and wrote: http://hackage.haskell.org/packages/archive/explicit-exception/0.1.4/doc/htm...
I find that having pattern match desugar to "fail", and supporting fail, can lead to extremely concise, clear code. For example, an excerpt from some type checking/inference code I wrote: data Equal a b = (a ~ b) => Refl data Typ a where TInt :: Typ Int TBool :: Typ Bool TList :: Typ a -> Typ [a] TArrow :: Typ a -> Typ b -> Typ (a -> b) eqT :: Typ a -> Typ b -> Maybe (Equal a b) eqT TInt TInt = return Refl eqT TBool TBool = return Refl eqT (TList a) (TList b) = do Refl <- eqT a b return Refl eqT (TArrow a1 a2) (TArrow b1 b2) = do Refl <- eqT a1 b1 Refl <- eqT a2 b2 return Refl eqT _ _ = fail "not equal" This relies heavily on the pattern match desugaring to "case", which brings the type equality (a ~ b) into scope, and "fail" returning Nothing. For example, the list case: desugaring eqT (TList TInt) (TList TInt), with all operations on the Maybe monad inlined and simplified we have ta = TList TInt :: Typ a, tb :: TList TInt :: Typ b, for some a, b eqT = case ta of ... (TList ta1) -> -- now we have a ~ [a1] for some a1 case tb of ... (TList tb1) -> -- now we have b ~ [b1] for some b1 case eqT ta1 tb1 of Just Refl -> -- now we have a1 ~ b1, which gives us [a1] ~ [b1], which gives us a ~ b Just Refl _ -> Nothing -- ryan
participants (3)
-
Henning Thielemann
-
John Millikin
-
Ryan Ingram