valida-base-0.2.0: Simple applicative validation for product types, batteries included!
Copyright(c) TotallyNotChase 2021
LicenseMIT
Maintainertotallynotchase42@gmail.com
StabilityStable
PortabilityPortable
Safe HaskellSafe
LanguageHaskell2010

Valida

Description

This module exports the primary validator building functions. It also exports all of Valida.Combinators.

Refer to the hackage documentation for function reference and examples. You can also find examples in the README, and also in the github repo, within the examples directory.

Synopsis

Documentation

type Selector a b = a -> b Source #

Convenience alias for functions that "select" a record field.

Primary data types

data Validation e a Source #

Like Either, but accumulates failures upon applicative composition.

Constructors

Failure e

Represents a validation failure with an error.

Success a

Represents a successful validation with the validated value.

Instances

Instances details
Bitraversable Validation Source # 
Instance details

Defined in Valida.Validation

Methods

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

Bifoldable Validation Source #
bifoldMap
bifoldMap is the same as validation.

Examples

bifoldMap (and its more generalized version, validation) can eliminate the need to pattern match on Validation.

>>> import Data.Bifoldable
>>> bifoldMap reverse (:[]) (Success 'c' :: Validation String Char)
"c"
>>> bifoldMap reverse (:[]) (Failure "error" :: Validation String Char)
"rorre"
Instance details

Defined in Valida.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 #

Bifunctor Validation Source # 
Instance details

Defined in Valida.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 #

Functor (Validation e) Source #
fmap
fmap maps given function over a Success value, does nothing on Failure value.

Examples

>>> fmap (+1) (Success 2)
Success 3
>>> fmap (+1) (Failure "error")
Failure "error"
Instance details

Defined in Valida.Validation

Methods

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

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

Semigroup e => Applicative (Validation e) Source #
pure
pure is a Success value.
(<*>)
(<*>) behaves similar to Either, but accumulates failures instead of stopping.

Examples

>>> pure 2 :: Validation String Int
Success 2
>>> Success (+1) <*> Success 4
Success 5
>>> Success (+1) <*> Failure "error"
Failure "error"
>>> Failure ["err1"] <*> Failure ["err2"]
Failure ["err1","err2"]
Instance details

Defined in Valida.Validation

Methods

pure :: a -> Validation e a #

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

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

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

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

Foldable (Validation e) Source #
foldMap
foldMap maps given function over a Success value, returns mempty for a Failure value.

Examples

>>> foldMap (:[]) (Success 2)
[2]
>>> foldMap (:[]) (Failure "error")
[]
Instance details

Defined in Valida.Validation

Methods

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

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

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

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

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

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

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

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

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

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

null :: Validation e a -> Bool #

length :: Validation e a -> Int #

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

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

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

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

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

Traversable (Validation e) Source #
traverse
In case of Success, traverse applies given function to the inner value, and maps Success over the result. In case of Failure, traverse returns Failure, wrapped in minimal context of the corresponding type (pure).

Examples

>>> traverse Just (Success 2)
Just (Success 2)
>>> traverse Just (Failure "error")
Just (Failure "error")
Instance details

Defined in Valida.Validation

Methods

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

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

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

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

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

Defined in Valida.Validation

Methods

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

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

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

Defined in Valida.Validation

Methods

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

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

toConstr :: Validation e a -> Constr #

dataTypeOf :: Validation e a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Valida.Validation

Methods

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

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

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

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

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

max :: Validation e a -> Validation e a -> Validation e a #

min :: Validation e a -> Validation e a -> Validation e a #

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

Defined in Valida.Validation

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

Defined in Valida.Validation

Methods

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

show :: Validation e a -> String #

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

Generic (Validation e a) Source # 
Instance details

Defined in Valida.Validation

Associated Types

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

Methods

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

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

Semigroup e => Semigroup (Validation e a) Source #
(<>)
This behaves similar to the Either semigroup. i.e Returns the first Success. But also accumulates Failures.

Examples

>>> Success 1 <> Success 2
Success 1
>>> Failure "error" <> Success 1
Success 1
>>> Success 2 <> Failure "error"
Success 2
>>> Failure ["err1"] <> Failure ["err2"]
Failure ["err1","err2"]
Instance details

Defined in Valida.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 #

type Rep (Validation e a) Source # 
Instance details

Defined in Valida.Validation

type Rep (Validation e a) = D1 ('MetaData "Validation" "Valida.Validation" "valida-base-0.2.0-HNh8G9pWsExKURHcoRZ8bQ" 'False) (C1 ('MetaCons "Failure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :+: C1 ('MetaCons "Success" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data ValidationRule e a Source #

The rule a Validator uses to run validation.

Contains a function that accepts the target type and returns a Validation result.

The type- ValidationRule (NonEmpty String) Int, designates a rule that verifies the validity of an Int, and uses a value of type NonEmpty String to represent error, in case of failure.

Instances

Instances details
Generic (ValidationRule e a) Source # 
Instance details

Defined in Valida.ValidationRule

Associated Types

type Rep (ValidationRule e a) :: Type -> Type #

Methods

from :: ValidationRule e a -> Rep (ValidationRule e a) x #

to :: Rep (ValidationRule e a) x -> ValidationRule e a #

Semigroup (ValidationRule e a) Source #
(<>)
(<>) creates a new ValidationRule that only succeeds when both given rule succeed. Otherwise left-most failure is returned.

Examples

>>> runValidator (validate (failureIf even "IsEven" <> failureIf (>9) "GreaterThan9")) 5
Success 5
>>> runValidator (validate (failureIf even "IsEven" <> failureIf (>9) "GreaterThan9")) 4
Failure ("IsEven" :| [])
>>> runValidator (validate (failureIf even "IsEven" <> failureIf (>9) "GreaterThan9")) 15
Failure ("GreaterThan9" :| [])
>>> runValidator (validate (failureIf even "IsEven" <> failureIf (>9) "GreaterThan9")) 12
Failure ("IsEven" :| [])
Instance details

Defined in Valida.ValidationRule

Monoid (ValidationRule e a) Source #
mempty
mempty is a ValidationRule that always succeeds.

Examples

>>> runValidator (validate mempty) 'a'
Success 'a'
Instance details

Defined in Valida.ValidationRule

type Rep (ValidationRule e a) Source # 
Instance details

Defined in Valida.ValidationRule

type Rep (ValidationRule e a) = D1 ('MetaData "ValidationRule" "Valida.ValidationRule" "valida-base-0.2.0-HNh8G9pWsExKURHcoRZ8bQ" 'True) (C1 ('MetaCons "ValidationRule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> Validation e ()))))

data Validator e inp a Source #

An applicative validator. Validates a predicate on an input when run and returns the Validation result.

Instances

Instances details
Functor (Validator e inp) Source #
fmap
fmap maps given function over the Validation result by re-using fmap on it.

Examples

>>> runValidator (fmap (+1) (validate $ failureIf (==2) "IsTwo")) 3
Success 4
>>> runValidator (fmap (+1) (validate $ failureIf (==2) "IsTwo")) 2
Failure ("IsTwo" :| [])
Instance details

Defined in Valida.Validator

Methods

fmap :: (a -> b) -> Validator e inp a -> Validator e inp b #

(<$) :: a -> Validator e inp b -> Validator e inp a #

Semigroup e => Applicative (Validator e inp) Source #
pure
pure creates a Validator that always yields given value wrapped in Success, ignoring its input.
(<*>)
(<*>) runs 2 validators to obtain the 2 Validation results and combines them with (<*>). This can be understood as-
(Validator ff) <*> (Validator v) = Validator (\inp -> ff inp <*> v inp)

i.e Run ff and v on the input, and compose the Validation results with (<*>).

Examples

>>> runValidator (pure 5) 42
Success 5
>>> let v1 = validate (failureIf (==2) "IsTwo")
>>> let v2 = validate (failureIf even "IsEven")
>>> runValidator (const <$> v1 <*> v2) 5
Success 5
>>> runValidator (const <$> v1 <*> v2) 4
Failure ("IsEven" :| [])
>>> runValidator (const <$> v1 <*> v2) 2
Failure ("IsTwo" :| ["IsEven"])
Instance details

Defined in Valida.Validator

Methods

pure :: a -> Validator e inp a #

(<*>) :: Validator e inp (a -> b) -> Validator e inp a -> Validator e inp b #

liftA2 :: (a -> b -> c) -> Validator e inp a -> Validator e inp b -> Validator e inp c #

(*>) :: Validator e inp a -> Validator e inp b -> Validator e inp b #

(<*) :: Validator e inp a -> Validator e inp b -> Validator e inp a #

Generic (Validator e inp a) Source # 
Instance details

Defined in Valida.Validator

Associated Types

type Rep (Validator e inp a) :: Type -> Type #

Methods

from :: Validator e inp a -> Rep (Validator e inp a) x #

to :: Rep (Validator e inp a) x -> Validator e inp a #

Semigroup e => Semigroup (Validator e inp a) Source #
(<>)
(<>) applies input over both validator functions, and combines the Validation results using (<>).

Examples

This essentially reuses the (<>) impl of Validation. i.e Returns the first Success. But also accumulates Failures.

>>> let v1 = validate (failureIf (==2) "IsTwo")
>>> let v2 = validate (failureIf even "IsEven")
>>> runValidator (v1 <> v2) 5
Success 5
>>> runValidator (v1 <> v2) 4
Success 4
>>> runValidator (v1 <> v2) 2
Failure ("IsTwo" :| ["IsEven"])
Instance details

Defined in Valida.Validator

Methods

(<>) :: Validator e inp a -> Validator e inp a -> Validator e inp a #

sconcat :: NonEmpty (Validator e inp a) -> Validator e inp a #

stimes :: Integral b => b -> Validator e inp a -> Validator e inp a #

type Rep (Validator e inp a) Source # 
Instance details

Defined in Valida.Validator

type Rep (Validator e inp a) = D1 ('MetaData "Validator" "Valida.Validator" "valida-base-0.2.0-HNh8G9pWsExKURHcoRZ8bQ" 'True) (C1 ('MetaCons "Validator" 'PrefixI 'True) (S1 ('MetaSel ('Just "runValidator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (inp -> Validation e a))))

Functions for building Valida data types

validate :: ValidationRule e a -> Validator e a a Source #

Build a basic validator from a ValidationRule.

The Validator runs the rule on its input. If validation is successful, the input is put into the Validation result.

validate rule = verify rule id

verify :: ValidationRule e b -> Selector a b -> Validator e a b Source #

Build a validator from a ValidationRule and a Selector.

The Validator first runs given selector on its input to obtain the validation target. Then, it runs the ValidationRule on the target.

If validation is successful, the validation target is put into the Validation result.

Examples

Expand

This is the primary function for building validators for your record types. To validate a pair, the most basic record type, such that the first element is a non empty string, and the second element is a number greater than 9, you can use:

>>> let pairValidator = (,) <$> verify (notEmpty "EmptyString") fst <*> verify (failureIf (<10) "LessThan10") snd

You can then run the validator on your input, using runValidator: >>> runValidator pairValidator ("foo", 12) Success ("foo",12) >>> runValidator pairValidator ("", 12) Failure (EmptyString :| []) >>> runValidator pairValidator ("foo", 9) Failure (LessThan10 :| []) >>> runValidator pairValidator ("", 9) Failure (EmptyString :| [LessThan10])

vrule :: (a -> Validation e ()) -> ValidationRule e a Source #

Low level function to manually build a ValidationRule. You should use the combinators instead.

Examples

Expand
>>> runValidator (validate (vrule (\x -> if isDigit x then Success () else Failure "NotDigit"))) 'a'
Failure "NotDigit"
>>> runValidator (validate (vrule (\x -> if isDigit x then Success () else Failure "NotDigit"))) '5'
Success '5'

(-?>) :: Selector a b -> ValidationRule e b -> Validator e a b infix 5 Source #

A synonym for verify with its arguments flipped.

Reassigning errors

label :: e -> ValidationRule x a -> ValidationRule e a Source #

Relabel a ValidationRule with a different error.

Many combinators, like failureIf' and failureUnless', simply return the given error value within NonEmpty upon failure. You can use label to override this return value.

Examples

Expand
>>> let rule = label "NotEven" (failureUnless' even)
>>> runValidator (validate rule) 1
Failure "NotEven"
>>> let rule = label "DefinitelyNotEven" (failureUnless even "NotEven")
>>> runValidator (validate rule) 1
Failure "DefinitelyNotEven"

labelV :: e -> Validator x inp a -> Validator e inp a Source #

Relabel a Validator with a different error.

Examples

Expand
>>> let validator = labelV "NotEven" (validate (failureUnless' even))
>>> runValidator validator 1
Failure "NotEven"
>>> let validator = labelV "DefinitelyNotEven" (validate (failureUnless even "NotEven"))
>>> runValidator validator 1
Failure "DefinitelyNotEven"

(<?>) :: ValidationRule x a -> e -> ValidationRule e a infix 6 Source #

A synonym for label with its arguments flipped.

(<??>) :: Validator x inp a -> e -> Validator e inp a infix 0 Source #

A synonym for labelV with its arguments flipped.

Re-exports of Valida.Combinators

Transformations between Either and Validation

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

Convert a Either to an Validation.

Given, Either e a-

  • Left e is converted to Failure e.
  • Right a is converted to Success a.

Examples

Expand
>>> fromEither (Right 'c' :: Either String Char)
Success 'c'
>>> fromEither (Left 42 :: Either Int Char)
Failure 42

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

Convert a Validation to an Either.

Given, Validation a b-

  • Failure a is converted to Left a.
  • Success b is converted to Right b.

Examples

Expand
>>> toEither (Success 'c' :: Validation String Char)
Right 'c'
>>> toEither (Failure 42 :: Validation Int Char)
Left 42

Utilities for working with Validation

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

Case analysis for Validation, i.e catamorphism.

In case of 'Failure e', apply the first function to e; in case of 'Success a', apply the second function to a.

This is a more generalized version of the bifoldMap implementation.

Examples

Expand
>>> validation (const Nothing) Just (Success 'c' :: Validation String Char)
Just 'c'
>>> validation (const Nothing) Just (Failure "error" :: Validation String Char)
Nothing

validationConst :: p -> p -> Validation e a -> p Source #

Case analysis for Validation, with replacer.

This is similar to validation, but takes in replacers instead of functions.

In case of Failure, return the first argument; otherwise, return the second argument.

validationConst e a = validation (const e) (const a)

Examples

Expand
>>> validation (const Nothing) Just (Success 'c' :: Validation String Char)
Just 'c'
>>> validation (const Nothing) Just (Failure "error" :: Validation String Char)
Nothing

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

Return the contents of a Success-value or a default value otherwise.

Examples

Expand
>>> fromSuccess 0 (Success 48 :: Validation Int Int)
48
>>> fromSuccess 0 (Failure 27 :: Validation Int Int)
0

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

Return the contents of a Failure-value or a default value otherwise.

Examples

Expand
>>> fromFailure 0 (Success 48 :: Validation Int Int)
0
>>> fromFailure 0 (Failure 27 :: Validation Int Int)
27

isSuccess :: Validation e a -> Bool Source #

Return True if the given value is a Success-value, False otherwise.

isFailure :: Validation e a -> Bool Source #

Return True if the given value is a Failure-value, False otherwise.

successes :: [Validation e a] -> [a] Source #

Extracts from a list of Validation all the Success elements, in order.

Examples

Expand
>>> successes [Success 1, Failure "err1", Failure "err2", Success 2, Failure "err3"]
[1,2]
>>> successes ([Failure "err1", Failure "err2", Failure "err3"] :: [Validation String Int])
[]

failures :: [Validation e a] -> [e] Source #

Extracts from a list of Validation all the Failure values, in order.

Examples

Expand
>>> failures [Success 48, Failure "err1", Failure "err2", Success 2, Failure "err3"]
["err1","err2","err3"]
>>> failures ([Success 1, Success 2, Success 3] :: [Validation String Int])
[]

partitionValidations :: [Validation e a] -> ([e], [a]) Source #

Partitions a list of Either into two lists.

All the Left elements are extracted, in order, to the first component of the output. Similarly the Right elements are extracted to the second component of the output.

partitionValidations xs = (failures xs, successes xs)

Examples

Expand
>>> partitionValidations [Success 1, Failure "err1", Failure "err2", Success 2, Failure "err3"]
(["err1","err2","err3"],[1,2])