Fail with class
This post describes a very common failure pattern using MonadFail. It also introduces a
small and hopefully useful FailT library that plays well with the MonadFail type class
and makes dealing with failures just a bit easier.
Introduction
There are a number of ways to fail and recover from errors in Haskell. They range from a
simple Maybe approach to an elaborate runtime exception mechanism, each with its own
pros and cons. This, however, is not the topic of our discussion today. Instead we
will drill into just one of those widely used failure patterns, in particular the one that
relies on the
MonadFail
type class:
class Monad m => MonadFail m where
fail :: String -> m a
History
It is worth doing a short history lesson about MonadFail, which will likely
be a recap for most. This type class originally came to fruition with ghc-8.0, with a long
transition scheme that migrated the fail function from its original definition inside
the Monad type class into the MonadFail. Starting with ghc-8.8 the fail function has
been completely removed from the Monad type class. More on this migration can be found
on the MonadFail proposal
(MFP)
wiki page. The point I'd like to highlight from this history lesson is that the
MonadFail is a fairly recent addition, but the fail function has been around for a
very long time. It might be even the case that it came into being together with the
initial definition of the Monad type class, but don't quote me on that. It definitely
dates back at least as far as the Haskell 98
report.
Due to its age and simplicity the fail function historically has been used to indicate
failure, but not necessarily a critical failure. Even with inventions of other failure
handling interfaces like MonadThrow, MonadError, etc. it is still very commonly used
to this day, because it is simple and effective. In the matter of fact it is even ingrained
into the Haskell's desugarer. Any time there is a pattern match failure inside a do
syntax, the MonadFail instance for that monad will be invoked. For example:
-- | Return `Nothing` whenever a `Right` is supplied and `Just` value otherwise
leftToJust :: Either a b -> Maybe a
leftToJust e = do
Left r <- Just e
Just r
In the example above the MonadFail instance for Maybe will be used whenever e has
the Right value instead of the expected Left leading to the pattern match failure and
Nothing being returned.
MonadFail utility
Utilization of the MonadFail interface is notorious in parsing and decoding. Think of
your favorite serialization library and it is likely to have some decoder monad, which
will have its MonadFail instance used extensively. Here are a few libraries off the top
of my head that rely on this interface:
aeson,
attoparsec,
binary,
time,
etc. This list can go on for a while…
The great part about the omnipresence of MonadFail instances in this category of
libraries is that you can write one function that can fail and use it with all of those
libraries. Let's say for the sake of example we have a simple type called Hour, which can
take on values 0 through 23. There is a safe and straightforward way to convert an
Integer to an Hour using MonadFail:
newtype Hour = Hour Int8
deriving Show
mkHour :: MonadFail m => Integer -> m Hour
mkHour h
| h < 0 = fail $ "Hour cannot be negative, but got: " ++ show h
| h > 23 = fail $ "Hour cannot be higher than 23, but got: " ++ show h
| otherwise = pure $ Hour $ fromInteger h
This is awesome, because now we can use this mkHour function while decoding JSON,
deserializing blobs, parsing text, etc. Below are some examples on how would one go about
using mkHour with some of the common libraries:
Aeson
Define a FromJSON instance:
instance FromJSON Hour where
parseJSON = withScientific "Hour" $ \s -> do
unless (isInteger s) $ fail "Expected an Integer"
mkHour (truncate s)
Then we can parse JSON values in the usual way:
λ> :set -XOverloadedStrings
λ> import Data.Aeson (eitherDecode)
λ> eitherDecode "5" :: Either String Hour
Right (Hour 5)
λ> eitherDecode "[1,2,5,12]" :: Either String [Hour]
Right [Hour 1,Hour 2,Hour 5,Hour 12]
λ> eitherDecode "-5" :: Either String Hour
Left "Error in $: Hour cannot be negative, but got: -5"
λ> eitherDecode "25" :: Either String Hour
Left "Error in $: Hour cannot be higher than 23, but got: 25"
Binary
Define a Binary instance:
instance Binary Hour where
put (Hour h) = put h
get = mkHour . toInteger @Int8 =<< get
Deserialize from a ByteString:
λ> :set -XOverloadedStrings
λ> import Data.Binary (decode)
λ> decode "\5" :: Hour
Hour 5
λ> decode "\25" :: Hour
Hour *** Exception: Data.Binary.Get.runGet at position 1: Hour cannot be higher than 23, but got: 25
CallStack (from HasCallStack):
error, called at libraries/binary/src/Data/Binary/Get.hs:345:5 in binary-0.8.9.0:Data.Binary.Get
Attoparsec
There are no special type classes in
attoparsec, so we can just use it
directly within the
Parser monad:
λ> :set -XOverloadedStrings
λ> import Data.Attoparsec.ByteString (parseOnly)
λ> import Data.Attoparsec.ByteString.Char8 (decimal)
λ> parseOnly (decimal >>= mkHour) "5" :: Either String Hour
Right (Hour 5)
λ> parseOnly (decimal >>= mkHour) "25" :: Either String Hour
Left "Failed reading: Hour cannot be higher than 23, but got: 25"
The problem
It seems that we can always use mkHour to safely construct an Hour from a variety of
inputs. It is true, however there is a hiccup. The most simple case when we need to make
an Hour from a readily available Integer is much harder than it seems at first. In
order to explore our options on how to solve this we first need to look at the MonadFail
instances available to us in base:
λ> :i MonadFail
type MonadFail :: (* -> *) -> Constraint
class Monad m => MonadFail m where
fail :: String -> m a
{-# MINIMAL fail #-}
-- Defined in ‘Control.Monad.Fail’
instance MonadFail [] -- Defined in ‘Control.Monad.Fail’
instance MonadFail Maybe -- Defined in ‘Control.Monad.Fail’
instance MonadFail IO -- Defined in ‘Control.Monad.Fail’
Not too much, but we are in luck, we can use Maybe:
λ> mkHour @Maybe 2
Just (Hour 2)
λ> mkHour @Maybe 25
Nothing
That works pretty good, except when we need to learn the reason why the conversion has
failed. An IO monad could fit the bill during testing or debugging:
λ> mkHour 2
Hour 2
λ> mkHour (-5)
*** Exception: user error (Hour cannot be negative, but got: -5)
λ> mkHour 25
*** Exception: user error (Hour cannot be higher than 23, but got: 25)
But what about an exception-free way of retrieving the failure message?
Potential solutions
Surely there has to be an out of the box approach to fail gracefully from within a pure function and access the error message, similarly to how it was done in the parsing example.
The first question that comes to mind when thinking about this problem is: "Why is there
no MonadFail instance for Either String?" That would be an ideal
solution, wouldn't it? But there is no such instance! Surely it had to be an
oversight, right? I wish! For reasons that I will never understand, there was a pushback
from the community on introducing an instance for Either, see this ghc issue
#12160 and the relevant mailing list
discussion. Over
the years I am definitely not the only one who thought such instance would be very
useful. Here are some other relevant resources that I found online: a reddit
discussion
that lead nowhere and a Stack Overflow
question,
which was left unanswered for two years.
I believe this is one of those cases when a few people in the community that pushed back ended up screwing everyone over. I could rant more about the petty arguments listed against that instance, but I'd rather focus my efforts on finding an alternative solution.
Orphan instance?
The decision about not providing an instance for Either determined one thing for sure,
that Either itself is out of the question as a potential solution for our problem. The
suggestion of using an orphan instance for Either is totally unusable:
instance IsString s => MonadFail (Either s) where
fail = Left . fromString
That is because in theory anyone can define another instance in any of the dependencies and we end up with a duplicate instance build error simply by adding an import that directly or transitively brings such instance into scope.
Transformers
How about ExceptT? I've heard that one is good for dealing with failures. Let's take a
look at its MonadFail instance:
instance MonadFail m => MonadFail (ExceptT e m) where
fail = ExceptT . fail
Well, that's of no use. It just propagates the failure to the underlying monad m.
Surprisingly there used to be an odd duck by the name of ErrorT, that had the desired
behavior with respect to MonadFail, but it was deprecated a while back.
λ> :set -Wno-deprecations
λ> import Data.Functor.Identity
λ> import Control.Monad.Trans.Error
λ> runIdentity $ runErrorT @String $ mkHour 5
Right (Hour 5)
λ> runIdentity $ runErrorT @String $ mkHour 25
Left "Hour cannot be higher than 23, but got: 25"
λ> runIdentity $ runErrorT @String $ mkHour (-1)
Left "Hour cannot be negative, but got: -1"
In my opinion, the ErrorT type itself was not a disaster and did not necessarily have to
be deprecated. It was the Error type class and all of the bogus instances in the
Control.Monad.Trans.Error module that had to burned. That module even had Alternative
and MonadPlus orphan instances for Either! Who in their sane mind thought those were a
good idea? One way or another I am happy that the Control.Monad.Trans.Error module is
finally gone.
Invert the problem
Turns out that any further search for a possible solution in base or other libraries that
are wired with GHC does not bear fruit.
My laziness to find a solution for years pushed me towards a simple workaround, namely defining two functions instead of one:
mkHourEither :: Integer -> Either String Hour
mkHourEither h
| h < 0 = Left $ "Hour cannot be negative, but got: " ++ show h
| h > 23 = Left $ "Hour cannot be higher than 23, but got: " ++ show h
| otherwise = Right $ Hour $ fromInteger h
mkHour :: MonadFail m => Integer -> m Hour
mkHour = either fail pure . mkHourEither
This approach does work, but it is pretty annoying and it only works for functions that
are defined locally. Any function that comes from a third party library that is already
restricted to MonadFail still suffers from our problem.
Define a custom monad
Last two solutions I can think of are:
- Define a custom monad or newtype wrapper around an
Eithertype with an instance that does what we need. - Look for a library on Hackage that solves this problem.
Both of these are viable solutions. But…
Defining a custom type each time this problem arises is not an elegant solution, in my opinion. I would rather use something out of the box without repeating myself each time I run into this problem. With respect to the second option, there are indeed libraries out there that can help with this particular problem, but they are not ideal either. We'll talk more on both of these options towards the end of the blog post. For now let's get on to a proper solution.
Proper solution
I am happy to bring to you the FailT library. As the
package name suggests it contains yet another monad transformer FailT, which, as it
usually happens, has an Identity variant Fail:
λ> import Control.Monad.Trans.Fail.String (runFail)
λ> runFail (mkHour 5)
Right (Hour 5)
λ> runFail (mkHour (-5))
Left "Hour cannot be negative, but got: -5"
λ> runFail (mkHour 25)
Left "Hour cannot be higher than 23, but got: 25"
This blog post could have ended on this note, because that is exactly the solution I
personally was looking for, but that would be a bit disappointing, wouldn't it? There are
other cool features provided by FailT that are worth discussing.
Monad transformer
First and foremost FailT is a monad transformer that has all of the mtl
instances. This means you can insert it into your transformer stack and regain the ability
to fail gracefully when MonadFail is in use. Here is a contrived example of doing some
vector mutation in
ST
monad while tracking index with StateT:
import Control.Monad.ST (ST, runST)
import Control.Monad.State.Strict (StateT, evalStateT, get, lift, put, replicateM_)
import Control.Monad.Trans.Fail.String (FailT, runFailT, throwFailT)
import Data.Vector (Vector, freeze)
import Data.Vector.Mutable (MVector, new, write)
import Lib (Hour, mkHour)
setHourArray :: MVector s Hour -> FailT (StateT Int (ST s)) ()
setHourArray mVec = do
ix <- get
h <- mkHour $ toInteger ix
lift $ write mVec ix h
put (ix + 1)
hoursArrayEither :: Int -> Either String (Vector Hour)
hoursArrayEither n = runST $ do
mVec <- new (max 0 n)
res <- evalStateT (runFailT (replicateM_ n (setHourArray mVec))) 0
mapM (const (freeze mVec)) res
hoursArray :: Int -> Vector Hour
hoursArray n = runST $ do
mVec <- new (max 0 n)
evalStateT (throwFailT (replicateM_ n (setHourArray mVec))) 0
freeze mVec
Here we define two functions, one of which fails gracefully with Either and another with
a runtime exception with the help of
MonadThrow
type class instance for ST monad and a helper function
throwFailT.
λ> hoursArrayEither 5
Right [Hour 0,Hour 1,Hour 2,Hour 3,Hour 4]
λ> hoursArrayEither 25
Left "Hour cannot be higher than 23, but got: 24"
λ> hoursArrayEither (-5)
Right []
Note that fairly recently MonadFail instance for ST monad has been
removed,
so FailT can serve as an alternative way to convert a failure produced by MonadFail
into a runtime exception from within ST:
λ> hoursArray 5
[Hour 0,Hour 1,Hour 2,Hour 3,Hour 4]
λ> hoursArray (-5)
[]
λ> hoursArray 25
*** Exception: FailException
"Hour cannot be higher than 23, but got: 24"
CallStack (from HasCallStack):
...
Polymorphic error message
We all know that [Char] is far from being the most efficient representation for the
textual data. For that reason alone it might make more sense to use Text instead of
String for failure messages. That is precisely why there is also a
Control.Monad.Trans.Fail.Text module provided by the FailT package, which uses Text
instead of String for the failure type in all functions and types.
As the matter of fact, in order to not discriminate against other string-like types, the actual
FailT implementation from Control.Monad.Trans.Fail is polymorphic in the message
failure type. Here is the full definition of the transformer, where e is the failure
type:
newtype FailT e m a = FailT (m (Either [e] a))
The API provides a few functions which restrict the failure type parameter e to
IsString or Show or both. For this reason it can be used with other string-like types
that have a more efficient Monoid instance, such as some sort of Builder for
example. It is even possible to use FailT with other failure types that don't have an
IsString instance, but that is possible only when MonadFail is not being used. All
three modules are pretty much drop-in replacements of each other and they all use the same
underlying type
FailT
Monad and Alternative instances
Using monadic interface with FailT is natural and straightforward, because it allows us
to stop the computation upon the very first failure:
λ> runFailT (fail "Bad action" >> pure ())
Left "Bad action"
However, what if we have a situation where we want to stop upon the very first success,
instead of a failure? In other words we would like to try a bunch of things and see what
sticks. This is exactly what the Alternative instance is for. Let's assume we have a
list with numbers as input that potentially represent hours and we'd like to get the very
first valid Hour:
λ> import Control.Monad.Trans.Fail.String (runFailT)
λ> import Control.Applicative (asum, empty)
λ> runFailT $ asum $ map mkHour [56, 25, -1, 4, 5, 22]
Right (Hour 4)
Very nice! Nonetheless, those that are familiar with Alternative type class will likely
have a question or two: "What do we get on empty? What happens when all of the values
that were supplied are invalid?" The answer depends on how the FailT is run. While going
through each individual attempt every failure is collected into a list, but when we use
runFailT all of the failure messages are combined together with a comma delimited
concatenation:
λ> runFailT $ asum $ map mkHour [25, -1]
Left "Hour cannot be higher than 23, but got: 25, Hour cannot be negative, but got: -1"
In case when the list is empty, i.e. upon usage of empty, a default error message is
produced:
λ> runFailT $ asum $ map mkHour []
Left "No failure reason given"
λ> runFailT (empty :: FailT IO ())
Left "No failure reason given"
Delimiting with a comma is a somewhat arbitrary decision and is not always a suitable one,
therefore we need to account for some other potential ways of dealing with aggregated
failures. This is done with
runFailAggT,
which returns all failure messages as a list:
λ> import Control.Monad.Trans.Fail.String (runFailAggT)
λ> runFailAggT (empty :: FailT IO ())
Left []
λ> runFailAggT (fail "" :: FailT IO ())
Left [""]
λ> Left msgs <- runFailAggT $ asum $ map mkHour [25, -1]
λ> mapM_ putStrLn msgs
Hour cannot be higher than 23, but got: 25
Hour cannot be negative, but got: -1
It is not uncommon for a function to produce the same failure message regardless of the
input that it was supplied with, in which case we might care only about the last failure
message. This can be done with
runFailLastT:
λ> runFailLastT $ asum $ map mkHour []
Left "No failure reason given"
λ> runFailLastT (fail "Bad" <|> fail "Bad" <|> fail "Bad" :: FailT IO ())
Left "Bad"
I would also like to point out that Either type does not have an Alternative instance,
which means it would be possible to use Fail instead whenever such instance is desired.
Monoid instance
Another hypothetical scenario we can think of is when we want to execute all of the
actions without any short circuiting. This is where the Monoid instance comes into play
and we can concatenate all of the actions together. As before, it will collect all of the
failures into a list, for the case when all of the attempts do fail, and combine all of
the successful results using a Semigroup instance of a result type. For example, if we
would like to run our mkHour on a whole bunch of input and simply count how many of the
conversions were successful, we could do it like so:
λ> import Control.Monad.Trans.Fail.String (runFail)
λ> import Data.Monoid (Sum(..))
λ> getSum <$> runFail (foldMap ((Sum (1 :: Int) <$) . mkHour) [10..100])
Right 14
MonadPlus instance
There can be no valid MonadPlus instance for FailT, because the "right zero" law
cannot be satisfied without sacrificing loss of information about the failure messages:
mzero >>= f = mzero -- left zero
m >> mzero = mzero -- right zero
That is because the only way that law can be satisfied is if we were to set fail _ =
mzero, which would make FailT totally useless in my opinion. This is not a problem for
an Alternative instance, because it does not have such a law. Moreover there is no need
to create an identical instance, as it is commonly the case with MonadPlus and
Alternative.
Alternative solutions
Let's now come back to our point of alternative solutions.
Custom type
It is quite reasonable to define a custom data type:
data Fail a = Fail String | Success a
This will certainly work, but it requires a lot of boilerplate. All the instances and
helper functions must be implemented from scratch. A slightly simpler approach would be to
use a newtype wrapper around Either:
newtype Fail a = Fail {runFail :: Either String a}
deriving newtype (Functor, Applicative, Monad)
instance MonadFail Fail where
fail = Fail . Left
This would work just fine for solving our original problem of recovering the failure
message from the mkHour function, but all of the other useful features described in this
post would not be available.
After a bit of digging through the web I've noticed that the most commonly suggested
solution is to define a newtype wrapper around ExceptT String m a:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Applicative
import Control.Monad.Trans.Except
import Control.Monad.Trans
import Data.Functor.Identity
newtype FailT m a = FailT (ExceptT String m a)
deriving (Functor, Applicative, Monad, MonadTrans)
runFailT :: FailT m a -> m (Either String a)
runFailT (FailT m) = runExceptT m
instance Monad m => MonadFail (FailT m) where
fail = FailT . throwE
This certainly works. We could even further derive all of the mtl instances, thus
avoiding quite a bit of boilerplate.
Third-party library
It is more than likely that I missed some libraries, but here are the two that I found on Hackage, which were designed specifically for this particular purpose:
Both of these take the same approach of relying on ExceptT as was described above. Thus
both of them are limited to the String type for failure messages. Below are some of the
other downsides that I found. Please note that this is just my subjective opinion and I am
not trying to convince others to agree with me:
-
om-failhas a few limitations:- Depends on
monad-logger, which brings in some baggage in the form of transitive dependencies. - Lacks instances for
mtltype classes, which limits its usability as a transformer. - There are no
AlternativeorSemigroupinstances, because they can't sensibly be defined with failure type restricted toString.
- Depends on
-
either-resulthas a few critical mistakes:-
The
Alternativeinstance is derived. This leads to the issue of unusable failure messages, because they are simply concatenated together, eg.:λ> import Control.Monad.Trans.Result λ> import Control.Applicative ((<|>)) λ> runResultT (fail "this action failed" <|> fail "that action failed" :: ResultT IO ()) Error "this action failedthat action failed" MonadPlusis also derived. As mentioned earlier in this post, this leads to an unlawful instance.- The
MonadErrorinstance is defined in such a way that mimics the one forExceptT, instead of being lifted into the underlying monad, as it is the case withFailT. Such implementation preventsResultTfrom being used together withExceptTin the same transformer stack. It is also defined as an orphan for some strange reason.
-
I am definitely not trying to speak ill of those libraries or undermine any of the work that the authors put into their design. I am simply justifying to myself and possibly to others why I went with writing my own library instead of reusing an existing one.
Conclusion
From what I know, MonadFail is far from being the most loved way to handle failures in
Haskell. Whether we like it or not, it is being used a lot. Threfore, since we are stuck
with it, might as well make the experience working with it a bit more pleasant.
This problem has been a stone in my shoe for some time. I am pretty happy to finally have it out. Hopefully others can benefit from this little library. Please send my way your suggestions, bug reports and pull requests on Github.