FailT-0.1.2.0: A 'FailT' monad transformer that plays well with 'MonadFail'
Copyright(c) Alexey Kuleshevich 2022-2023
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Trans.Fail.Text

Description

This module contains a synonym for FailT e m a transformer, where failure type e is restricted to Text. All functions in this module have the same names and are a drop-in replacement for Control.Monad.Trans.Fail module, except with monomorphic failure type.

Synopsis

Documentation

type Fail = Fail Text Source #

Version of Fail restricted to Text

runFail :: Fail a -> Either Text a Source #

Version of runFail restricted to Text

runFailLast :: Fail a -> Either Text a Source #

Version of runFailLast restricted to Text

runFailAgg :: Fail a -> Either [Text] a Source #

Version of runFailAgg restricted to Text

errorFail :: HasCallStack => Fail a -> a Source #

Version of errorFail restricted to Text

Throw an error if there was a failure, otherwise return the result of monadic computation. Use throwFailT in case you'd like to handle an actual exception.

errorFailWithoutStackTrace :: Fail a -> a Source #

Version of errorFailWithoutStackTrace restricted to Text

Same as errorFail, but without the stack trace:

>>> errorFailWithoutStackTrace (fail "This didn't work" :: Fail ())
*** Exception: "This didn't work"
>>> import Control.Applicative
>>> errorFailWithoutStackTrace (fail "This didn't work" <|> pure "That Worked" :: Fail String)
"That Worked"

type FailT = FailT Text Source #

Version of FailT restricted to Text

Fail monad transformer that plays well with MonadFail

data FailException where Source #

An exception that is produced by the FailT monad transformer.

Constructors

FailException 

Fields

failT :: Applicative m => Text -> FailT m a Source #

Version of failT restricted to Text

Monomorphic synonym for fail

failManyT :: Applicative m => [Text] -> FailT m a Source #

Version of failManyT restricted to Text

Since: 0.1.2

runFailT :: Functor m => FailT m a -> m (Either Text a) Source #

Version of runFailT restricted to Text

runFailLastT :: Functor m => FailT m a -> m (Either Text a) Source #

Version of runFailLastT restricted to Text

runFailAggT :: FailT m a -> m (Either [Text] a) Source #

Version of runFailAggT restricted to Text

hoistFailT :: (forall a. m a -> n a) -> FailT m b -> FailT n b Source #

Version of hoistFailT restricted to Text

Change the underlying monad with the hoisting function

mapFailT :: (m (Either [Text] a) -> n (Either [Text] b)) -> FailT m a -> FailT n b Source #

Version of mapFailT restricted to Text

Map a function over the underlying representation of the FailT monad.

mapErrorFailT :: Functor m => (e -> Text) -> FailT e m a -> FailT m a Source #

Version of mapErrorFailT where resulting type is restricted to Text

Map a function over the error type in the FailT monad.

mapErrorsFailT :: Functor m => ([e] -> [Text]) -> FailT e m a -> FailT m a Source #

Version of mapErrorsFail, where resulting type is restricted to Text

Map a function over the aggregation of errors in the FailT monad. Could be used for example for clearing our all of the aggregated error messages:

>>> runFail (mapErrorsFailT (const [] :: [Text] -> [Text]) $ fail "Something went wrong" >> pure ())
Left "No failure reason given"

exceptFailT :: (HasCallStack, Monad m) => FailT m a -> ExceptT FailException m a Source #

Version of exceptFailT restricted to Text

throwErrorFailT :: (HasCallStack, MonadError FailException m) => FailT m a -> m a Source #

Version of throwErrorFailT restricted to Text

Same as exceptFailT, but works with any MonadError.

>>> import Control.Monad.Trans.Fail.Text
>>> throwErrorFailT (fail "A bad thing" >> pure () :: FailT (Except FailException) ())
ExceptT (Identity (Left FailException
"A bad thing"
CallStack (from HasCallStack):
...

throwFailT :: (HasCallStack, MonadThrow m) => FailT m a -> m a Source #

Version of throwFailT restricted to Text