Copyright | (c) Alexey Kuleshevich 2022-2023 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module contains a synonym for
transformer, where failure
type FailT
e m ae
is restricted to
. 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.Text
Synopsis
- type Fail = Fail Text
- runFail :: Fail a -> Either Text a
- runFailLast :: Fail a -> Either Text a
- runFailAgg :: Fail a -> Either [Text] a
- errorFail :: HasCallStack => Fail a -> a
- errorFailWithoutStackTrace :: Fail a -> a
- type FailT = FailT Text
- data FailException where
- FailException :: (Typeable e, Show e) => {..} -> FailException
- failT :: Applicative m => Text -> FailT m a
- runFailT :: Functor m => FailT m a -> m (Either Text a)
- runFailLastT :: Functor m => FailT m a -> m (Either Text a)
- runFailAggT :: FailT m a -> m (Either [Text] a)
- hoistFailT :: (forall a. m a -> n a) -> FailT m b -> FailT n b
- mapFailT :: (m (Either [Text] a) -> n (Either [Text] b)) -> FailT m a -> FailT n b
- mapErrorFailT :: Functor m => (e -> Text) -> FailT e m a -> FailT m a
- mapErrorsFailT :: Functor m => ([e] -> [Text]) -> FailT e m a -> FailT m a
- exceptFailT :: (HasCallStack, Monad m) => FailT m a -> ExceptT FailException m a
- throwFailT :: (HasCallStack, MonadThrow m) => FailT m a -> m a
Documentation
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"
data FailException where Source #
An exception that is produced by the FailT
monad transformer.
FailException | |
|
Instances
Exception FailException Source # | |
Defined in Control.Monad.Trans.Fail | |
Show FailException Source # | |
Defined in Control.Monad.Trans.Fail showsPrec :: Int -> FailException -> ShowS # show :: FailException -> String # showList :: [FailException] -> ShowS # |
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
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
throwFailT :: (HasCallStack, MonadThrow m) => FailT m a -> m a Source #
Version of throwFailT
restricted to Text