validation-0.6.3: A data-type like Either but with an accumulating Applicative

Safe HaskellSafe
LanguageHaskell2010

Data.Validation

Contents

Description

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

Synopsis

Data type

data AccValidation err a Source #

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

A consequence of this is that AccValidation 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

AccFailure err 
AccSuccess a 

Instances

Bitraversable AccValidation Source # 

Methods

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

Bifoldable AccValidation Source # 

Methods

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

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

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

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

Bifunctor AccValidation Source # 

Methods

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

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

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

Swapped AccValidation Source # 

Methods

swapped :: (Profunctor p, Functor f) => p (AccValidation b a) (f (AccValidation d c)) -> p (AccValidation a b) (f (AccValidation c d)) #

Validate AccValidation Source # 

Methods

_AccValidation :: (Profunctor p, Functor f) => p (AccValidation e a) (f (AccValidation g b)) -> p (AccValidation e a) (f (AccValidation g b)) Source #

_Either :: (Profunctor p, Functor f) => p (Either e a) (f (Either g b)) -> p (AccValidation e a) (f (AccValidation g b)) Source #

Functor (AccValidation err) Source # 

Methods

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

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

Semigroup err => Applicative (AccValidation err) Source # 

Methods

pure :: a -> AccValidation err a #

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

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

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

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

Foldable (AccValidation err) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: AccValidation err a -> Bool #

length :: AccValidation err a -> Int #

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

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

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

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

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

Traversable (AccValidation err) Source # 

Methods

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

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

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

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

Semigroup err => Apply (AccValidation err) Source # 

Methods

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

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

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

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

Alt (AccValidation err) Source # 

Methods

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

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

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

(Eq a, Eq err) => Eq (AccValidation err a) Source # 

Methods

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

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

(Data a, Data err) => Data (AccValidation err a) Source # 

Methods

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

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

toConstr :: AccValidation err a -> Constr #

dataTypeOf :: AccValidation err a -> DataType #

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

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

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

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

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

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

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

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

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

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

(Ord a, Ord err) => Ord (AccValidation err a) Source # 

Methods

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

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

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

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

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

max :: AccValidation err a -> AccValidation err a -> AccValidation err a #

min :: AccValidation err a -> AccValidation err a -> AccValidation err a #

(Show a, Show err) => Show (AccValidation err a) Source # 

Methods

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

show :: AccValidation err a -> String #

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

Generic (AccValidation err a) Source # 

Associated Types

type Rep (AccValidation err a) :: * -> * #

Methods

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

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

Semigroup e => Semigroup (AccValidation e a) Source # 
Monoid e => Monoid (AccValidation e a) Source # 
(NFData e, NFData a) => NFData (AccValidation e a) Source # 

Methods

rnf :: AccValidation e a -> () #

type Rep (AccValidation err a) Source # 
type Rep (AccValidation err a) = D1 * (MetaData "AccValidation" "Data.Validation" "validation-0.6.3-CSPvpyi6uIE6gAWwi5DcUl" False) ((:+:) * (C1 * (MetaCons "AccFailure" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * err))) (C1 * (MetaCons "AccSuccess" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

Constructing validations

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

validates the a with the given predicate, returning e if the predicate does not hold.

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

validate :: e -> (a -> Bool) -> a -> AccValidation e a

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

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

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

Converts from Either to AccValidation.

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

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

Functions on validations

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

validation is the catamorphism for AccValidation.

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

Converts from AccValidation to Either.

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

v orElse a returns a when v is AccFailure, and the a in AccSuccess a.

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

orElse :: AccValidation 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) -> AccValidation e a -> a

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

ensure leaves the validation unchanged when the predicate holds, or fails with e otherwise.

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

ensure :: e -> (a -> Bool) -> AccValidation e a -> AccValidation e a

codiagonal :: AccValidation a a -> a Source #

codiagonal gets the value out of either side.

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

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

This can be thought of as having the type

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

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

bindValidation binds through an AccValidation, which is useful for composing AccValidations sequentially. Note that despite having a bind function of the correct type, AccValidation 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 AccValidation. 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 AccValidation.

_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 AccValidation.

Isomorphisms

class Validate f where Source #

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

Minimal complete definition

_AccValidation

Methods

_AccValidation :: Iso (f e a) (f g b) (AccValidation e a) (AccValidation g b) Source #

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

Instances

Validate Either Source # 

Methods

_AccValidation :: (Profunctor p, Functor f) => p (AccValidation e a) (f (AccValidation g b)) -> p (Either e a) (f (Either g b)) Source #

_Either :: (Profunctor p, Functor f) => p (Either e a) (f (Either g b)) -> p (Either e a) (f (Either g b)) Source #

Validate AccValidation Source # 

Methods

_AccValidation :: (Profunctor p, Functor f) => p (AccValidation e a) (f (AccValidation g b)) -> p (AccValidation e a) (f (AccValidation g b)) Source #

_Either :: (Profunctor p, Functor f) => p (Either e a) (f (Either g b)) -> p (AccValidation e a) (f (AccValidation 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.