Error Monad and strings

Reading the Control.Monad.Error documentation, I see that the Error class has noMsg and strMsg as its only two functions. Now, I understand that you can define your own Error instances such as in example 1 of the documentation, so why the need to always support strings via noMsg/strMsg ? What uses these? And if in my code, I will never throw an error with a string, am I supposed to implement these functions and then ignore them?

It is for the very annoying reason that in order for Error to be a monad it has to implement the "fail" method, which means it has to know how to turn an arbitrary string into a value of your error type. Cheers, Greg On 07/27/10 15:32, Gerald Gutierrez wrote:
Reading the Control.Monad.Error documentation, I see that the Error class has noMsg and strMsg as its only two functions.
Now, I understand that you can define your own Error instances such as in example 1 of the documentation, so why the need to always support strings via noMsg/strMsg ? What uses these? And if in my code, I will never throw an error with a string, am I supposed to implement these functions and then ignore them?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The "strMsg" method is used to implement the "fail" method in the resulting method, and calls to "fail" might be inserted into your code even if you don't explicitly call it. An example in GHCi: Prelude> :m + Control.Monad.Error Prelude Control.Monad.Error> do { Just x <- return Nothing ; return x } :: Either String Int Left "Pattern match failure in do expression at <interactive>:1:5-8" Note that in the "Either String" monad, "failStr" is equal to "Left". On 2010 July 27, at 15:32, Gerald Gutierrez wrote:
Reading the Control.Monad.Error documentation, I see that the Error class has noMsg and strMsg as its only two functions.
Now, I understand that you can define your own Error instances such as in example 1 of the documentation, so why the need to always support strings via noMsg/strMsg ? What uses these? And if in my code, I will never throw an error with a string, am I supposed to implement these functions and then ignore them?

On Tue, Jul 27, 2010 at 3:57 PM, Dietrich Epp
The "strMsg" method is used to implement the "fail" method in the resulting method, and calls to "fail" might be inserted into your code even if you don't explicitly call it. An example in GHCi: Prelude> :m + Control.Monad.Error Prelude Control.Monad.Error> do { Just x <- return Nothing ; return x } :: Either String Int Left "Pattern match failure in do expression at <interactive>:1:5-8"
On 2010 July 27, at 15:32, Gerald Gutierrez wrote:
Reading the Control.Monad.Error documentation, I see that the Error class has noMsg and strMsg as its only two functions. Now, I understand that you can define your own Error instances such as in example 1 of the documentation, so why the need to always support strings via noMsg/strMsg ? What uses these? And if in my code, I will never throw an error with a string, am I supposed to implement these functions and then ignore them?
I see. So strings must be supported in the case of a bug which cannot be caught at compile time? In other words, if I get an error with a string, I'm pretty much guaranteed it is a bug, i.e. a pattern match error as the "fail" documentation says.

I'll say yes, a pattern match failure is a bug. This is one of the great debates in the language: whether all pattern matching code should be guaranteed complete at compile time or not. However, any function you call which returns a result in your monad could theoretically call "fail" if it was written that way. Data.Map.lookup used to call "fail" when it could not find a key, but that got changed. If you don't want to catch these errors in your monad, you can write your own monad (or monad transformer). For example: newtype ErrorCode = ErrorCode Int deriving Show newtype ErrorCodeT m a = ErrorCodeT { runErrorCodeT :: m (Either ErrorCode a) } instance Monad m => Monad (ErrorCodeT m) where return = ErrorCodeT . return . Right a >>= b = ErrorCodeT $ do m <- runErrorCodeT a case m of Left err -> return $ Left err Right x -> runErrorCodeT $ b x fail = ErrorCodeT . fail failWithCode :: Monad m => Int -> ErrorCodeT m a failWithCode = ErrorCodeT . return . Left . ErrorCode There's probabaly a library somewhere which does this already. On 2010 July 27, at 16:08, Gerald Gutierrez wrote:
I see. So strings must be supported in the case of a bug which cannot be caught at compile time? In other words, if I get an error with a string, I'm pretty much guaranteed it is a bug, i.e. a pattern match error as the "fail" documentation says.

On Tue, Jul 27, 2010 at 6:29 PM, Dietrich Epp
I'll say yes, a pattern match failure is a bug. This is one of the great debates in the language: whether all pattern matching code should be guaranteed complete at compile time or not. However, any function you call which returns a result in your monad could theoretically call "fail" if it was written that way. Data.Map.lookup used to call "fail" when it could not find a key, but that got changed.
I've always thought that being able to write:
catMaybes :: [Maybe a] -> [a] catMaybes xs = [ x | Just x <- xs ]
is really cool, which relies on:
fail _ = []
being in the Monad instance for List. But I would give that up for getting "fail" out of Monad. We can alway re-implement "catMaybes." Antoine

I've always thought that being able to write:
catMaybes :: [Maybe a] -> [a] catMaybes xs = [ x | Just x <- xs ]
is really cool, which relies on:
fail _ = []
being in the Monad instance for List.
Really? I thought that's just a feature of list comprehensions. List comps are not monads, at least not any more. If you wrote it as: catMaybes xs = do Just x <- xs return x Then yes, I believe that uses 'fail'.

On Tue, Jul 27, 2010 at 04:08:39PM -0700, Gerald Gutierrez wrote:
Reading the Control.Monad.Error documentation, I see that the Error class has noMsg and strMsg as its only two functions. Now, I understand that you can define your own Error instances such as in example 1 of the documentation, so why the need to always support strings via noMsg/strMsg ? What uses these? And if in my code, I will never throw an error with a string, am I supposed to implement these functions and then ignore them?
I see. So strings must be supported in the case of a bug which cannot be caught at compile time? In other words, if I get an error with a string, I'm pretty much guaranteed it is a bug, i.e. a pattern match error as the "fail" documentation says.
Not at all, depending on the properties of your monad and intent, a pattern match failure may or may not be considered a bug, So write your instance appropriately. it is perfectly fine to make pattern match failure be 'error' if that is what is appropriate for your monad and usage. However, the instance definition for Either that mentions Error is definitely a big misfeature in the library. Non-local returns are generally useful in many contexts other than errors. Actually, the 'Error' class in general seems somewhat dubious to me. I would avoid using or depending on it. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
participants (6)
-
Antoine Latter
-
Dietrich Epp
-
Evan Laforge
-
Gerald Gutierrez
-
Gregory Crosswhite
-
John Meacham