FailT: A 'FailT' monad transformer that plays well with 'MonadFail'

[ bsd3, control, failure, library ] [ Propose Tags ] [ Report a vulnerability ]

Fail gracefully when stuck in a MonadFail

>>> runFailT (fail "Failure!?" >> pure "Success!!")
Left "Failure!?"
>>> runFailT (fail "Failure!?" <|> pure "Success!!")
Right "Success!!"
>>> runFailT (pure ["Success!!"] <> fail "Failure!?" <> pure ["At", "Last!"])
Right ["Success!!","At","Last!"]

[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.1.0, 0.1.2.0 (info)
Change log CHANGELOG.md
Dependencies base (>=4.9 && <5), exceptions, mtl, text [details]
Tested with ghc ==8.0.2, ghc ==8.2.2, ghc ==8.4.4, ghc ==8.6.5, ghc ==8.8.4, ghc ==8.10.7, ghc ==9.0.2, ghc ==9.2.5, ghc ==9.4.4
License BSD-3-Clause
Copyright 2022-2023 Alexey Kuleshevich
Author Alexey Kuleshevich
Maintainer alexey@kuleshevi.ch
Category Control, Failure
Home page https://github.com/lehins/FailT
Source repo head: git clone https://github.com/lehins/FailT
Uploaded by lehins at 2023-02-24T22:29:51Z
Distributions LTSHaskell:0.1.2.0, NixOS:0.1.2.0, Stackage:0.1.2.0
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 2580 total (9 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2023-02-24 [all 1 reports]

Readme for FailT-0.1.2.0

[back to package description]

FailT

This package solves a fairly simple, but very common problem of gracefully converting a monadic computation that uses MonadFail into either a result or a string failure message(s).

Github Actions Coveralls Hackage Nightly LTS
GA-CI Coveralls Hackage Nightly LTS

Motivation

When we have a function that can fail in a MonadFail, there is no instance in base that would allow us to get the failure message without a runtime exception. It is best to demonstrate the problem with an example.

Here is formatParseM function from the time package, which is designed to parse time:

formatParseM :: MonadFail m => Format t -> String -> m t

We can use it out of the box with various packages like aeson, attoparsec, binary, etc. Here is how it could be used to successfully parse a string with time in the IO monad:

λ> import Data.Time (UTCTime)
λ> import Data.Time.Format.ISO8601 (formatParseM, iso8601Format)
λ> formatParseM iso8601Format "2023-01-08T00:29:00Z" :: IO UTCTime
2023-01-08 00:29:00 UTC

However, when it comes to bad input, there is not a single monad in base or other package that is wired with GHC that has a MonadFail instance, which would allow us to gracefully fail and retrieve the error message. Below are all the instances from base:

λ> formatParseM iso8601Format "Bad time" :: IO UTCTime
*** Exception: user error (no parse of "Bad time")
λ> formatParseM iso8601Format "Bad time" :: Maybe UTCTime
Nothing
λ> formatParseM iso8601Format "Bad time" :: [UTCTime]
[]

Solution

This is where FailT package comes to help:

λ> import Control.Monad.Trans.Fail.String
λ> runFail $ formatParseM iso8601Format "Bad time" :: Either String UTCTime
Left "no parse of \"Bad time\""
λ> runFail $ formatParseM iso8601Format "2023-01-08T00:29:00Z" :: Either String UTCTime
Right 2023-01-08 00:29:00 UTC

Features

Monad transformer

Naturally, as the package name suggests, it provides a FailT monad transformer.

The example above used the Fail type synonym, whcih is restricts the underlying monad to Identity. Below is the example of running FailT with IO:

λ> import Control.Monad.IO.Class
λ> runFailT (liftIO . print . utctDayTime =<< formatParseM iso8601Format "2023-01-08T00:29:00Z")
1740s
Right ()
λ> runFailT (liftIO . print . utctDayTime =<< formatParseM iso8601Format "Bad input")
Left "no parse of \"Bad input\""

Polymorphic failure

Thus far examples only showed using String type for failure messages, but that is not a requirement. This library was designed to be agnostic with respect to failure message type with restriction to IsString type class. Reason for the constraint is because the failure message normally originates with the fail function and is string like by its nature:

fail :: MonadFail m => String -> m ()

The more general implementation is located in import Control.Monad.Trans.Fail, which contains polymorphic implementation that allows the user to choose a more specific type for the failure type e:

runFailT :: (IsString e, Semigroup e, Functor m) => FailT e m a -> m (Either e a)

This package implements convenience modules:

  • Control.Monad.Trans.Fail.String
  • Control.Monad.Trans.Fail.Text

which provide type synonyms and functions with more restricted failure types: String and Text respectfully. Modules were designed to be drop-in replacements of each other.

Convenient instances

There are many type class instances for FailT monad. Such as instances for type classes from mtl package, MonadIO instance, etc. Most of them rely on the instances of the underlying monad by lifting the functionality. However, here are some of the more notable and useful instances that do not require corresponding instances from the underlying monad:

  • MonadFail with Monadic sequencing, which allow to stop the computation upon the first invocation of fail.

    λ> runFailT (fail "Failure!?" >> pure "Success!!")
    Left "Failure!?"
    
  • Alternative, which will continue until the first successful computation is encountered.

    λ> runFailT (fail "Failure!?" <|> pure "Success!!")
    Right "Success!!"
    
  • Semigroup and Monoid, which will not stop until all of the actions are executed. Produced at the end are either all of the failures or the results of all of the successful cases combined with <>

    λ> runFailT (pure ["Success!!"] <> fail "Failure!?" <> pure ["At", "Last!"])
    Right ["Success!!","At","Last!"]
    λ> runFailT mempty :: IO (Either String ())
    Left "No failure reason given"