validation-1.1.2: A data-type like Either but with an accumulating Applicative
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Validation

Description

A data type similar to Data.Either that accumulates failures.

Synopsis

Data type

data Validation err a Source #

A Validation is either a value of the type err or a, similar to Either. However, the Applicative instance for Validation accumulates errors using a Semigroup on err. In contrast, the Applicative for Either returns only the first error.

A consequence of this is that Validation has no Bind or Monad instance. This is because such an instance would violate the law that a Monad's ap must equal the Applicative's <*>

An example of typical usage can be found here.

Constructors

Failure err 
Success a 

Instances

Instances details
Bifunctor Validation Source # 
Instance details

Defined in Data.Validation

Methods

bimap :: (a -> b) -> (c -> d) -> Validation a c -> Validation b d #

first :: (a -> b) -> Validation a c -> Validation b c #

second :: (b -> c) -> Validation a b -> Validation a c #

Swap Validation Source # 
Instance details

Defined in Data.Validation

Methods

swap :: Validation a b -> Validation b a #

Bitraversable Validation Source # 
Instance details

Defined in Data.Validation

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Validation a b -> f (Validation c d) #

Bifoldable Validation Source # 
Instance details

Defined in Data.Validation

Methods

bifold :: Monoid m => Validation m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Validation a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Validation a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Validation a b -> c #

Validate Validation Source # 
Instance details

Defined in Data.Validation

Methods

_Validation :: Iso (Validation e a) (Validation g b) (Validation e a) (Validation g b) Source #

_Either :: Iso (Validation e a) (Validation g b) (Either e a) (Either g b) Source #

Functor (Validation err) Source # 
Instance details

Defined in Data.Validation

Methods

fmap :: (a -> b) -> Validation err a -> Validation err b #

(<$) :: a -> Validation err b -> Validation err a #

Semigroup err => Applicative (Validation err) Source # 
Instance details

Defined in Data.Validation

Methods

pure :: a -> Validation err a #

(<*>) :: Validation err (a -> b) -> Validation err a -> Validation err b #

liftA2 :: (a -> b -> c) -> Validation err a -> Validation err b -> Validation err c #

(*>) :: Validation err a -> Validation err b -> Validation err b #

(<*) :: Validation err a -> Validation err b -> Validation err a #

Foldable (Validation err) Source # 
Instance details

Defined in Data.Validation

Methods

fold :: Monoid m => Validation err m -> m #

foldMap :: Monoid m => (a -> m) -> Validation err a -> m #

foldMap' :: Monoid m => (a -> m) -> Validation err a -> m #

foldr :: (a -> b -> b) -> b -> Validation err a -> b #

foldr' :: (a -> b -> b) -> b -> Validation err a -> b #

foldl :: (b -> a -> b) -> b -> Validation err a -> b #

foldl' :: (b -> a -> b) -> b -> Validation err a -> b #

foldr1 :: (a -> a -> a) -> Validation err a -> a #

foldl1 :: (a -> a -> a) -> Validation err a -> a #

toList :: Validation err a -> [a] #

null :: Validation err a -> Bool #

length :: Validation err a -> Int #

elem :: Eq a => a -> Validation err a -> Bool #

maximum :: Ord a => Validation err a -> a #

minimum :: Ord a => Validation err a -> a #

sum :: Num a => Validation err a -> a #

product :: Num a => Validation err a -> a #

Traversable (Validation err) Source # 
Instance details

Defined in Data.Validation

Methods

traverse :: Applicative f => (a -> f b) -> Validation err a -> f (Validation err b) #

sequenceA :: Applicative f => Validation err (f a) -> f (Validation err a) #

mapM :: Monad m => (a -> m b) -> Validation err a -> m (Validation err b) #

sequence :: Monad m => Validation err (m a) -> m (Validation err a) #

Semigroup err => Apply (Validation err) Source # 
Instance details

Defined in Data.Validation

Methods

(<.>) :: Validation err (a -> b) -> Validation err a -> Validation err b #

(.>) :: Validation err a -> Validation err b -> Validation err b #

(<.) :: Validation err a -> Validation err b -> Validation err a #

liftF2 :: (a -> b -> c) -> Validation err a -> Validation err b -> Validation err c #

Alt (Validation err) Source #

For two errors, this instance reports only the last of them.

Instance details

Defined in Data.Validation

Methods

(<!>) :: Validation err a -> Validation err a -> Validation err a #

some :: Applicative (Validation err) => Validation err a -> Validation err [a] #

many :: Applicative (Validation err) => Validation err a -> Validation err [a] #

(Eq err, Eq a) => Eq (Validation err a) Source # 
Instance details

Defined in Data.Validation

Methods

(==) :: Validation err a -> Validation err a -> Bool #

(/=) :: Validation err a -> Validation err a -> Bool #

(Data err, Data a) => Data (Validation err a) Source # 
Instance details

Defined in Data.Validation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Validation err a -> c (Validation err a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Validation err a) #

toConstr :: Validation err a -> Constr #

dataTypeOf :: Validation err a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Validation err a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Validation err a)) #

gmapT :: (forall b. Data b => b -> b) -> Validation err a -> Validation err a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Validation err a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Validation err a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Validation err a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Validation err a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) #

(Ord err, Ord a) => Ord (Validation err a) Source # 
Instance details

Defined in Data.Validation

Methods

compare :: Validation err a -> Validation err a -> Ordering #

(<) :: Validation err a -> Validation err a -> Bool #

(<=) :: Validation err a -> Validation err a -> Bool #

(>) :: Validation err a -> Validation err a -> Bool #

(>=) :: Validation err a -> Validation err a -> Bool #

max :: Validation err a -> Validation err a -> Validation err a #

min :: Validation err a -> Validation err a -> Validation err a #

(Show err, Show a) => Show (Validation err a) Source # 
Instance details

Defined in Data.Validation

Methods

showsPrec :: Int -> Validation err a -> ShowS #

show :: Validation err a -> String #

showList :: [Validation err a] -> ShowS #

Generic (Validation err a) Source # 
Instance details

Defined in Data.Validation

Associated Types

type Rep (Validation err a) :: Type -> Type #

Methods

from :: Validation err a -> Rep (Validation err a) x #

to :: Rep (Validation err a) x -> Validation err a #

Semigroup e => Semigroup (Validation e a) Source # 
Instance details

Defined in Data.Validation

Methods

(<>) :: Validation e a -> Validation e a -> Validation e a #

sconcat :: NonEmpty (Validation e a) -> Validation e a #

stimes :: Integral b => b -> Validation e a -> Validation e a #

Monoid e => Monoid (Validation e a) Source # 
Instance details

Defined in Data.Validation

Methods

mempty :: Validation e a #

mappend :: Validation e a -> Validation e a -> Validation e a #

mconcat :: [Validation e a] -> Validation e a #

(NFData e, NFData a) => NFData (Validation e a) Source # 
Instance details

Defined in Data.Validation

Methods

rnf :: Validation e a -> () #

type Rep (Validation err a) Source # 
Instance details

Defined in Data.Validation

type Rep (Validation err a) = D1 ('MetaData "Validation" "Data.Validation" "validation-1.1.2-GqOgT3tVLnu7ibVErKH3Ml" 'False) (C1 ('MetaCons "Failure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 err)) :+: C1 ('MetaCons "Success" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Constructing validations

validate :: Validate v => e -> (a -> Maybe b) -> a -> v e b Source #

validates an a producing an updated optional value, returning e in the empty case.

This can be thought of as having the less general type:

validate :: e -> (a -> Maybe b) -> a -> Validation e b

validationNel :: Either e a -> Validation (NonEmpty e) a Source #

validationNel is liftError specialised to NonEmpty lists, since they are a common semigroup to use.

fromEither :: Either e a -> Validation e a Source #

Converts from Either to Validation.

liftError :: (b -> e) -> Either b a -> Validation e a Source #

liftError is useful for converting an Either to an Validation when the Left of the Either needs to be lifted into a Semigroup.

Functions on validations

validation :: (e -> c) -> (a -> c) -> Validation e a -> c Source #

validation is the catamorphism for Validation.

toEither :: Validation e a -> Either e a Source #

Converts from Validation to Either.

orElse :: Validate v => v e a -> a -> a Source #

v orElse a returns a when v is Failure, and the a in Success a.

This can be thought of as having the less general type:

orElse :: Validation e a -> a -> a

valueOr :: Validate v => (e -> a) -> v e a -> a Source #

Return the a or run the given function over the e.

This can be thought of as having the less general type:

valueOr :: (e -> a) -> Validation e a -> a

ensure :: Validate v => e -> (a -> Maybe b) -> v e a -> v e b Source #

ensure ensures that a validation remains unchanged upon failure, updating a successful validation with an optional value that could fail with e otherwise.

This can be thought of as having the less general type:

ensure :: e -> (a -> Maybe b) -> Validation e a -> Validation e b

codiagonal :: Validation a a -> a Source #

codiagonal gets the value out of either side.

validationed :: Validate v => (v e a -> v e' a') -> Validation e a -> Validation e' a' Source #

Run a function on anything with a Validate instance (usually Either) as if it were a function on Validation

This can be thought of as having the type

(Either e a -> Either e' a') -> Validation e a -> Validation e' a'

bindValidation :: Validation e a -> (a -> Validation e b) -> Validation e b Source #

bindValidation binds through a Validation, which is useful for composing Validations sequentially. Note that despite having a bind function of the correct type, Validation is not a monad. The reason is, this bind does not accumulate errors, so it does not agree with the Applicative instance.

There is nothing wrong with using this function, it just does not make a valid Monad instance.

Prisms

These prisms are useful for writing code which is polymorphic in its choice of Either or Validation. This choice can then be made later by a user, depending on their needs.

An example of this style of usage can be found here

_Failure :: Validate f => Prism (f e1 a) (f e2 a) e1 e2 Source #

This prism generalises _Left. It targets the failure case of either Either or Validation.

_Success :: Validate f => Prism (f e a) (f e b) a b Source #

This prism generalises _Right. It targets the success case of either Either or Validation.

Isomorphisms

class Validate f where Source #

The Validate class carries around witnesses that the type f is isomorphic to Validation, and hence isomorphic to Either.

Minimal complete definition

_Validation

Methods

_Validation :: Iso (f e a) (f g b) (Validation e a) (Validation g b) Source #

_Either :: Iso (f e a) (f g b) (Either e a) (Either g b) Source #

Instances

Instances details
Validate Either Source # 
Instance details

Defined in Data.Validation

Methods

_Validation :: Iso (Either e a) (Either g b) (Validation e a) (Validation g b) Source #

_Either :: Iso (Either e a) (Either g b) (Either e a) (Either g b) Source #

Validate Validation Source # 
Instance details

Defined in Data.Validation

Methods

_Validation :: Iso (Validation e a) (Validation g b) (Validation e a) (Validation g b) Source #

_Either :: Iso (Validation e a) (Validation g b) (Either e a) (Either g b) Source #

revalidate :: (Validate f, Validate g) => Iso (f e1 s) (f e2 t) (g e1 s) (g e2 t) Source #

revalidate converts between any two instances of Validate.