[Haskell-cafe] Error Monad and strings
Dietrich Epp
depp at zdome.net
Tue Jul 27 19:29:54 EDT 2010
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.
More information about the Haskell-Cafe
mailing list