monad-validate-1.2.0.1: A monad transformer for data validation.
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Validate.Class

Synopsis

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:

  1. Unlike throwError, raising an error using refute does not always abort the entire computation—it may only abort a local part of it.
  2. Unlike tell, raising an error using dispute still causes the computation to globally fail, it just doesn’t affect local execution.

Instances must obey the following law:

disputevoid . tolerate . refute

For a more thorough explanation, with examples, see the documentation for ValidateT.

Minimal complete definition

refute, tolerate

Methods

refute :: e -> m a Source #

Raises a fatal validation error. Aborts the current branch of the validation (i.e. does not return).

>>> runValidate (refute ["boom"] >> refute ["bang"])
Left ["boom"]

dispute :: e -> m () Source #

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 void . tolerate . refute (which must behave equivalently by law), but it is sometimes possible to provide a more efficient implementation.

tolerate :: m a -> m (Maybe a) Source #

tolerate m behaves like m, 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

Instances details
MonadValidate e m => MonadValidate e (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> MaybeT m a Source #

dispute :: e -> MaybeT m () Source #

tolerate :: MaybeT m a -> MaybeT m (Maybe a) Source #

(MonadValidate e m, Monoid w) => MonadValidate e (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> WriterT w m a Source #

dispute :: e -> WriterT w m () Source #

tolerate :: WriterT w m a -> WriterT w m (Maybe a) Source #

(MonadTransControl t, Monad (t m), MonadValidate e m) => MonadValidate e (WrappedMonadTrans t m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

(MonadValidate e m, Monoid w) => MonadValidate e (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> WriterT w m a Source #

dispute :: e -> WriterT w m () Source #

tolerate :: WriterT w m a -> WriterT w m (Maybe a) Source #

(MonadValidate e m, Monoid w) => MonadValidate e (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> WriterT w m a Source #

dispute :: e -> WriterT w m () Source #

tolerate :: WriterT w m a -> WriterT w m (Maybe a) Source #

MonadValidate e m => MonadValidate e (StateT s m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> StateT s m a Source #

dispute :: e -> StateT s m () Source #

tolerate :: StateT s m a -> StateT s m (Maybe a) Source #

MonadValidate e m => MonadValidate e (StateT s m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> StateT s m a Source #

dispute :: e -> StateT s m () Source #

tolerate :: StateT s m a -> StateT s m (Maybe a) Source #

MonadValidate e m => MonadValidate e (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> ReaderT r m a Source #

dispute :: e -> ReaderT r m () Source #

tolerate :: ReaderT r m a -> ReaderT r m (Maybe a) Source #

MonadValidate e m => MonadValidate e (ExceptT a m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> ExceptT a m a0 Source #

dispute :: e -> ExceptT a m () Source #

tolerate :: ExceptT a m a0 -> ExceptT a m (Maybe a0) Source #

MonadValidate e m => MonadValidate e (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> IdentityT m a Source #

dispute :: e -> IdentityT m () Source #

tolerate :: IdentityT m a -> IdentityT m (Maybe a) Source #

(Monad m, Semigroup e) => MonadValidate e (ValidateT e m) Source # 
Instance details

Defined in Control.Monad.Validate.Internal

Methods

refute :: e -> ValidateT e m a Source #

dispute :: e -> ValidateT e m () Source #

tolerate :: ValidateT e m a -> ValidateT e m (Maybe a) Source #

(MonadValidate e m, Monoid w) => MonadValidate e (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> RWST r w s m a Source #

dispute :: e -> RWST r w s m () Source #

tolerate :: RWST r w s m a -> RWST r w s m (Maybe a) Source #

(MonadValidate e m, Monoid w) => MonadValidate e (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> RWST r w s m a Source #

dispute :: e -> RWST r w s m () Source #

tolerate :: RWST r w s m a -> RWST r w s m (Maybe a) Source #

(MonadValidate e m, Monoid w) => MonadValidate e (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

refute :: e -> RWST r w s m a Source #

dispute :: e -> RWST r w s m () Source #

tolerate :: RWST r w s m a -> RWST r w s m (Maybe a) Source #

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 (pure 42)
Right 42
>>> 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 (:[]) (pure 42)
Right 42
>>> 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

Instances

Instances details
(MonadTransControl t, Monad (t m), MonadValidate e m) => MonadValidate e (WrappedMonadTrans t m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

MonadTrans t => MonadTrans (WrappedMonadTrans t) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

lift :: Monad m => m a -> WrappedMonadTrans t m a #

MonadTransControl t => MonadTransControl (WrappedMonadTrans t) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Associated Types

type StT (WrappedMonadTrans t) a #

Methods

liftWith :: Monad m => (Run (WrappedMonadTrans t) -> m a) -> WrappedMonadTrans t m a #

restoreT :: Monad m => m (StT (WrappedMonadTrans t) a) -> WrappedMonadTrans t m a #

Monad (t m) => Monad (WrappedMonadTrans t m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

(>>=) :: WrappedMonadTrans t m a -> (a -> WrappedMonadTrans t m b) -> WrappedMonadTrans t m b #

(>>) :: WrappedMonadTrans t m a -> WrappedMonadTrans t m b -> WrappedMonadTrans t m b #

return :: a -> WrappedMonadTrans t m a #

Functor (t m) => Functor (WrappedMonadTrans t m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

fmap :: (a -> b) -> WrappedMonadTrans t m a -> WrappedMonadTrans t m b #

(<$) :: a -> WrappedMonadTrans t m b -> WrappedMonadTrans t m a #

Applicative (t m) => Applicative (WrappedMonadTrans t m) Source # 
Instance details

Defined in Control.Monad.Validate.Class

Methods

pure :: a -> WrappedMonadTrans t m a #

(<*>) :: WrappedMonadTrans t m (a -> b) -> WrappedMonadTrans t m a -> WrappedMonadTrans t m b #

liftA2 :: (a -> b -> c) -> WrappedMonadTrans t m a -> WrappedMonadTrans t m b -> WrappedMonadTrans t m c #

(*>) :: WrappedMonadTrans t m a -> WrappedMonadTrans t m b -> WrappedMonadTrans t m b #

(<*) :: WrappedMonadTrans t m a -> WrappedMonadTrans t m b -> WrappedMonadTrans t m a #

type StT (WrappedMonadTrans t) a Source # 
Instance details

Defined in Control.Monad.Validate.Class

type StT (WrappedMonadTrans t) a = StT t a