| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Control.Monad.Validate.Class
Synopsis
- class (Monad m, Semigroup e) => MonadValidate e m | m -> e where
- exceptToValidate :: forall e m a. MonadValidate e m => ExceptT e m a -> m a
- exceptToValidateWith :: forall e1 e2 m a. MonadValidate e2 m => (e1 -> e2) -> ExceptT e1 m a -> m a
- newtype WrappedMonadTrans (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (a :: Type) = WrapMonadTrans {
- unwrapMonadTrans :: t m a
Documentation
class (Monad m, Semigroup e) => MonadValidate e m | m -> e where Source #
The class of validation monads, intended to be used to validate data structures while collecting
errors along the way. In a sense, MonadValidate is like a combination of
MonadError and MonadWriter, but it isn’t
entirely like either. The two essential differences are:
- Unlike
throwError, raising an error usingrefutedoes not always abort the entire computation—it may only abort a local part of it. - Unlike
tell, raising an error usingdisputestill causes the computation to globally fail, it just doesn’t affect local execution.
Instances must obey the following law:
dispute≡void.tolerate.refute
For a more thorough explanation, with examples, see the documentation for
ValidateT.
Methods
Raises a fatal validation error. Aborts the current branch of the validation (i.e. does not return).
>>>runValidate(refute["boom"]>>refute["bang"])Left["boom"]
Raises a non-fatal validation error. The overall validation fails, and the error is recorded, but validation continues in an attempt to try and discover more errors.
>>>runValidate(dispute["boom"]>>dispute["bang"])Left["boom", "bang"]
If not explicitly implemented, the default implementation is (which must behave equivalently by law), but it is sometimes possible to provide a
more efficient implementation.void . tolerate .
refute
tolerate :: m a -> m (Maybe a) Source #
behaves like tolerate mm, except that any fatal errors raised by refute are altered
to non-fatal errors that return Nothing. This allows m’s result to be used for further
validation if it succeeds without preventing further validation from occurring upon failure.
>>>runValidate(tolerate(refute["boom"])>>refute["bang"])Left["boom", "bang"]
Since: 1.1.0.0
Instances
exceptToValidate :: forall e m a. MonadValidate e m => ExceptT e m a -> m a Source #
Runs an ExceptT computation, and if it raised an error, re-raises it using refute. This
effectively converts a computation that uses ExceptT (or MonadError) into
one that uses MonadValidate.
>>>runValidate$exceptToValidate(pure42)Right42 >>>runValidate$exceptToValidate(throwError["boom"])Left"boom"
Since: 1.2.0.0
exceptToValidateWith :: forall e1 e2 m a. MonadValidate e2 m => (e1 -> e2) -> ExceptT e1 m a -> m a Source #
Like exceptToValidate, but additionally accepts a function, which is applied to the error
raised by ExceptT before passing it to refute. This can be useful if the original error type is
not a Semigroup.
>>>runValidate$exceptToValidateWith(:[]) (pure42)Right42 >>>runValidate$exceptToValidateWith(:[]) (throwError"boom")Left["boom"]
Since: 1.2.0.0
Deriving MonadValidate instances with DerivingVia
newtype WrappedMonadTrans (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (a :: Type) Source #
If you have a monad transformer that implements the MonadTransControl class, this newtype
wrapper can be used to automatically derive instances of MonadValidate using the DerivingVia
GHC extension.
Example:
{-# LANGUAGE DerivingVia #-}
newtype CustomT c m a = CustomT { runCustomT :: ... }
deriving (MonadValidate e) via (WrappedMonadTrans (CustomT c) m)
Since: 1.2.0.0
Constructors
| WrapMonadTrans | |
Fields
| |