unpacked-validation-0.1.0.0: An unpacked validation data type

Safe HaskellNone
LanguageHaskell2010

Data.Validation.Unpacked

Contents

Description

 

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 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

Validation (#err | a#) 

Bundled Patterns

pattern Failure :: err -> Validation err a 
pattern Success :: a -> Validation err a 

Instances

Bitraversable Validation Source # 

Methods

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

Bifoldable Validation Source # 

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 #

Bifunctor Validation Source # 

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 #

Functor (Validation err) Source # 

Methods

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

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

Semigroup err => Applicative (Validation err) Source # 

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 # 

Methods

fold :: Monoid m => Validation err m -> 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 # 

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) #

(Eq a, Eq b) => Eq (Validation a b) Source # 

Methods

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

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

(Ord a, Ord b) => Ord (Validation a b) Source # 

Methods

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

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

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

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

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

max :: Validation a b -> Validation a b -> Validation a b #

min :: Validation a b -> Validation a b -> Validation a b #

(Read a, Read b) => Read (Validation a b) Source # 
(Show b, Show a) => Show (Validation a b) Source # 

Methods

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

show :: Validation a b -> String #

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

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

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 # 

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 # 

Methods

rnf :: Validation e a -> () #

Construction

failure :: err -> Validation err a Source #

This is the same as Failure.

success :: a -> Validation err a Source #

This is the same as Success.

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

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

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 #

Case analysis on Validation.

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

Converts from Validation to Either.

orElse :: Validation e a -> a -> a Source #

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

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

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

ensure :: e -> (a -> Bool) -> Validation e a -> Validation e a Source #

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

codiagonal :: Validation a a -> a Source #

codiagonal gets the value out of either side.

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

bindValidation binds through an 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.

Conversion

fromBaseValidation :: Validation a b -> Validation a b Source #

Convert validation's Validation to a Validation.

toBaseValidation :: Validation a b -> Validation a b Source #

Convert a Validation to validation's Validation.