validation-selective-0.1.0.1: Lighweight pure data validation based on Applicative and Selective functors
Copyright(c) 2014 Chris Allen Edward Kmett
(c) 2018-2021 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Validation

Description

Lightweight pure data validation based on Applicative and Selective functors.

Validation allows to accumulate all errors instead of short-circuting on the first error so you can display all possible errors at once.

Common use-cases include:

  1. Validating each input of a form with multiple inputs.
  2. Performing multiple validations of a single value.

Validation provides modular and composable interface which means that you can implement validations for different pieces of your data independently, and then combine smaller parts into the validation of a bigger type. The below table illustrates main ways to combine two Validations:

TypeclassOperation ○Failure e ○ Failure dSuccess a ○ Success bFailure e ○ Success aSuccess a ○ Failure e
Semigroup<>Failure (e <> d)Success (a <> b)Failure eFailure e
Applicative<*>Failure (e <> d)Success (a b)Failure eFailure e
Alternative<|>Failure (e <> d)Success aSuccess aSuccess a
Selective<*?Failure eSelective choiceFailure eSelective choice

In other words, instances of different standard typeclasses provide various semantics which can be useful in different use-cases:

  1. Semigroup: accumulate both Failure and Success with <>.
  2. Monoid: Success that stores mempty.
  3. Functor: change the type inside Success.
  4. Bifunctor: change both Failure and Success.
  5. Applicative: apply function to values inside Success and accumulate errors inside Failure.
  6. Alternative: return the first Success or accumulate all errors inside Failure.
  7. Selective: choose which validations to apply based on the value inside.
Synopsis

Type

data Validation e a Source #

Validation is a polymorphic sum type for storing either all validation failures or validation success. Unlike Either, which returns only the first error, Validation accumulates all errors using the Semigroup typeclass.

Usually type variables in Validation e a are used as follows:

  • e: is a list or set of failure messages or values of some error data type.
  • a: is some domain type denoting successful validation result.

Some typical use-cases:

  • Validation [String] User
    • Either list of String error messages or a validated value of a custom User type.
  • Validation (NonEmpty UserValidationError) User
    • Similar to previous example, but list of failures guaranteed to be non-empty in case of validation failure, and it stores values of some custom error type.

Constructors

Failure e

Validation failure. The e type is supposed to implement the Semigroup instance.

Success a

Successful validation result of type a.

Instances

Instances details
Bitraversable Validation Source #

Similar to Traversable but traverses both Failure and Success with given effectful computations.

Examples

>>> parseInt = readMaybe :: String -> Maybe Int
>>> bitraverse listToMaybe parseInt (Success "42")
Just (Success 42)
>>> bitraverse listToMaybe parseInt (Success "int")
Nothing
>>> bitraverse listToMaybe parseInt (Failure [15])
Just (Failure 15)
>>> bitraverse listToMaybe parseInt (Failure [])
Nothing
Instance details

Defined in Validation

Methods

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

Bifoldable Validation Source #

Similar to Foldable but allows folding both Failure and Success to the same monoidal value according to given functions.

Examples

>>> one x = [x]
>>> bifoldMap id (one . show) (Success 15)
["15"]
>>> bifoldMap id (one . show) (Failure ["Wrong", "Fail"])
["Wrong","Fail"]
Instance details

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

Similar to Functor but allows mapping of values inside both Failure and Success.

Examples

>>> bimap length show (Success 50)
Success "50"
>>> bimap length show (Failure ["15", "9"])
Failure 2
Instance details

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

NFData2 Validation Source # 
Instance details

Defined in Validation

Methods

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

(NoValidationMonadError, Semigroup e) => Monad (Validation e) Source #

⚠️CAUTION⚠️ This instance is for custom error display only.

It's not possible to implement lawful Monad instance for Validation.

In case it is used by mistake, the user will see the following:

>>> Success 42 >>= \n -> if even n then Success n else Failure ["Not even"]
...
... Type 'Validation' doesn't have lawful 'Monad' instance
      which means that you can't use 'Monad' methods with 'Validation'.
...
Instance details

Defined in Validation

Methods

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

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

return :: a -> Validation e a #

Functor (Validation e) Source #

Allows changing the value inside Success with a given function.

Examples

>>> fmap (+1) (Success 9)
Success 10
>>> fmap (+1) (Failure ["wrong"])
Failure ["wrong"]
Instance details

Defined in Validation

Methods

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

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

Semigroup e => Applicative (Validation e) Source #

This instance is the most important instance for the Validation data type. It's responsible for the many implementations. And it allows to accumulate errors while performing validation or combining the results in the applicative style.

Examples

>>> success1 = Success 9 :: Validation [String] Int
>>> success2 = Success 15 :: Validation [String] Int
>>> successF = Success (* 2) :: Validation [String] (Int -> Int)
>>> failure1 = Failure ["WRONG"] :: Validation [String] Int
>>> failure2 = Failure ["FAIL"]  :: Validation [String] Int
>>> successF <*> success1
Success 18
>>> successF <*> failure1
Failure ["WRONG"]
>>> (+) <$> success1 <*> success2
Success 24
>>> (+) <$> failure1 <*> failure2
Failure ["WRONG","FAIL"]
>>> liftA2 (+) success1 failure1
Failure ["WRONG"]
>>> liftA3 (,,) failure1 success1 failure2
Failure ["WRONG","FAIL"]

Implementations of all functions are lazy and they correctly work if some arguments are not fully evaluated.

>>> failure1 *> failure2
Failure ["WRONG","FAIL"]
>>> isFailure $ failure1 *> failure2
True
>>> epicFail = error "Impossible validation" :: Validation [String] Int
>>> isFailure $ failure1 *> epicFail
True
Instance details

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

Foldable for Validation allows folding values inside Success.

Examples

>>> fold (Success [16])
[16]
>>> fold (Failure "WRONG!" :: Validation String [Int])
[]
Instance details

Defined in 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 values inside Success with some effectful computation.

Examples

>>> parseInt = readMaybe :: String -> Maybe Int
>>> traverse parseInt (Success "42")
Just (Success 42)
>>> traverse parseInt (Success "int")
Nothing
>>> traverse parseInt (Failure ["42"])
Just (Failure ["42"])
Instance details

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

(Semigroup e, Monoid e) => Alternative (Validation e) Source #

This instance implements the behaviour when the first Success is returned. Otherwise all Failures are combined.

Examples

>>> success1 = Success [9] :: Validation [String] [Int]
>>> success2 = Success [15] :: Validation [String] [Int]
>>> failure1 = Failure ["WRONG"] :: Validation [String] [Int]
>>> failure2 = Failure ["FAIL"]  :: Validation [String] [Int]
>>> success1 <|> success2
Success [9]
>>> failure1 <|> failure2
Failure ["WRONG","FAIL"]
>>> failure2 <|> success2
Success [15]
Instance details

Defined in Validation

Methods

empty :: Validation e a #

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

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

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

NFData e => NFData1 (Validation e) Source # 
Instance details

Defined in Validation

Methods

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

Semigroup e => Selective (Validation e) Source #

Selective functors from the selective package. This instance allows choosing which validations to apply based on value inside. Validation can't have a lawful Monad instance but it's highly desirable to have the monadic behavior in cases when you want future checks depend on previous values. Selective allows to circumvent this limitation by providing the desired behavior.

Examples

Expand

To understand better, how Selective can be helpful, let's consider a typical usage example with validating passwords.

>>> :{
newtype Password = Password
    { unPassword :: String
    } deriving stock (Show)
:}

When user enters a password in some form, we want to check the following conditions:

  1. Password must not be empty.
  2. Password must contain at least 8 characters.
  3. Password must contain at least 1 digit.

As in the previous usage example with form validation, let's introduce a custom data type to represent all possible errors.

>>> :{
data PasswordValidationError
    = EmptyPassword
    | ShortPassword
    | NoDigitPassword
    deriving stock (Show)
:}

And, again, we can implement independent functions to validate all these cases:

>>> type PasswordValidation = Validation (NonEmpty PasswordValidationError) Password
>>> :{
validateEmptyPassword :: String -> PasswordValidation
validateEmptyPassword password = Password password <$
    failureIf (null password) EmptyPassword
:}
>>> :{
validateShortPassword :: String -> PasswordValidation
validateShortPassword password = Password password <$
    failureIf (length password < 8) ShortPassword
:}
>>> :{
validatePasswordDigit :: String -> PasswordValidation
validatePasswordDigit password = Password password <$
    failureUnless (any isDigit password) NoDigitPassword
:}

And we can easily compose all these checks into single validation for Password using Applicative instance:

>>> :{
validatePassword :: String -> PasswordValidation
validatePassword password =
    validateEmptyPassword password
    *> validateShortPassword password
    *> validatePasswordDigit password
:}

However, if we try using this function, we can notice a problem immediately:

>>> validatePassword ""
Failure (EmptyPassword :| [ShortPassword,NoDigitPassword])

Due to the nature of the Applicative instance for Validation, we run all checks and combine all possible errors. But you can notice that if password is empty, it doesn't make sense to run other validations. The fact that the password is empty implies that password is shorter than 8 characters.

You may say that check for empty password is redundant because empty password is a special case of a short password. However, when using Validation, we want to display readable and friendly errors to users, so they know how to fix errors and can act correspondingly.

This behaviour could be achieved easily if Validation had the Monad instance. But it can't have a lawful Monad instance. Fortunately, the Selective instance for Validation can help with our problem. But to solve it, we need to write our password validation in a slightly different way.

First, we need to write a function that checks whether the password is empty:

>>> :{
checkEmptyPassword :: String -> Validation e Bool
checkEmptyPassword = Success . null
:}

Now we can use the ifS function from the selective package to branch on the result of checkEmptyPassword:

>>> :{
validatePassword :: String -> PasswordValidation
validatePassword password = ifS
    (checkEmptyPassword password)
    (failure EmptyPassword)
    (validateShortPassword password *> validatePasswordDigit password)
:}

With this implementation we achieved our desired behavior:

>>> validatePassword ""
Failure (EmptyPassword :| [])
>>> validatePassword "abc"
Failure (ShortPassword :| [NoDigitPassword])
>>> validatePassword "abc123"
Failure (ShortPassword :| [])
>>> validatePassword "security567"
Success (Password {unPassword = "security567"})
Instance details

Defined in Validation

Methods

select :: Validation e (Either a b) -> Validation e (a -> b) -> Validation e b #

Generic1 (Validation e :: Type -> Type) Source # 
Instance details

Defined in Validation

Associated Types

type Rep1 (Validation e) :: k -> Type #

Methods

from1 :: forall (a :: k). Validation e a -> Rep1 (Validation e) a #

to1 :: forall (a :: k). Rep1 (Validation e) a -> Validation e a #

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

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

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

Defined in 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 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 a) => Semigroup (Validation e a) Source #

Semigroup allows merging multiple Validations into single one by combining values inside both Failure and Success. The <> operator merges two Validations following the below rules:

  1. If both values are Failures, returns a new Failure with accumulated errors.
  2. If both values are Successful, returns a new Success with combined success using Semigroup for values inside Success.
  3. If one value is Failure and another one is Success, then Failure is returned.

Examples

>>> success1 = Success [9] :: Validation [String] [Int]
>>> success2 = Success [15] :: Validation [String] [Int]
>>> failure1 = Failure ["WRONG"] :: Validation [String] [Int]
>>> failure2 = Failure ["FAIL"]  :: Validation [String] [Int]
>>> success1 <> success2
Success [9,15]
>>> failure1 <> failure2
Failure ["WRONG","FAIL"]
>>> success1 <> failure1
Failure ["WRONG"]
>>> failure2 <> success1 <> success2 <> failure1
Failure ["FAIL","WRONG"]
Instance details

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

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

mempty :: Validation e a is Success which stores mempty :: a to be consistent with the Semigroup instance.

Examples

>>> mempty :: Validation String [Bool]
Success []
Instance details

Defined in 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 Validation

Methods

rnf :: Validation e a -> () #

type Rep1 (Validation e :: Type -> Type) Source # 
Instance details

Defined in Validation

type Rep1 (Validation e :: Type -> Type) = D1 ('MetaData "Validation" "Validation" "validation-selective-0.1.0.1-inplace" '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) Par1))
type Rep (Validation e a) Source # 
Instance details

Defined in Validation

type Rep (Validation e a) = D1 ('MetaData "Validation" "Validation" "validation-selective-0.1.0.1-inplace" '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)))

How to use

This section contains the typical Validation usage example. Let's say we have a form with fields where you can input your login information.

>>> :{
data Form = Form
    { formUserName :: !String
    , formPassword :: !String
    }
:}

This Form data type can represent values of some text fields on the web page or inside the GUI application. Our goal is to create a value of the custom User data type from the Form fields.

First, let's define our User type and additional newtypes for more type safety.

>>> :{
newtype UserName = UserName
    { unUserName :: String
    } deriving newtype (Show)
:}
>>> :{
newtype Password = Password
    { unPassword :: String
    } deriving newtype (Show)
:}
>>> :{
data User = User
    { userName     :: !UserName
    , userPassword :: !Password
    } deriving stock (Show)
:}

We can easily create a User from the Form in the unsafe way by wrapping each form field into the corresponding newtype:

>>> :{
unsafeUserFromForm :: Form -> User
unsafeUserFromForm Form{..} = User
    { userName     = UserName formUserName
    , userPassword = Password formPassword
    }
:}

However, this conversion is unsafe (as name suggests) since Form can contain invalid data. So, before creating a User we want to check whether all Form fields satisfy our preconditions. Specifically:

  1. User name must not be empty.
  2. Password should be at least 8 characters long.
  3. Password should contain at least 1 digit.

Validation offers modular and composable way of defining and outputting all validation failures which means:

  1. Modular: define validation checks for different fields independently.
  2. Composable: combine smaller validations easily into a validation of a bigger type.

Before implementing Form validation, we need to introduce a type for representing our validation errors. It is a good practice to define all possible errors as a single sum type, so let's go ahead:

>>> :{
data FormValidationError
    = EmptyName
    | ShortPassword
    | NoDigitPassword
    deriving stock (Show)
:}

With Validation we can define checks for individual fields independently and compose them later. First, let's start with defining validation for the name:

>>> :{
validateName :: String -> Validation (NonEmpty FormValidationError) UserName
validateName name = UserName name <$ failureIf (null name) EmptyName
:}

You can notice a few things about this function:

  1. All errors are collected in NonEmpty, since we want to have guarantees that in case of errors we have at least one failure.
  2. It wraps the result into UserName to tell that validation is passed.

Let's see how this function works:

>>> validateName "John"
Success "John"
>>> validateName ""
Failure (EmptyName :| [])

Since Validation provides modular interface for defining checks, we now can define all validation functions for the password separately:

>>> :{
validateShortPassword :: String -> Validation (NonEmpty FormValidationError) Password
validateShortPassword password = Password password <$
    failureIf (length password < 8) ShortPassword
:}
>>> :{
validatePasswordDigit :: String -> Validation (NonEmpty FormValidationError) Password
validatePasswordDigit password = Password password <$
    failureUnless (any isDigit password) NoDigitPassword
:}

After we've implemented validations for different Form fields, it's time to combine them together! Validation offers several ways to compose different validations. These ways are provided via different instances of common Haskell typeclasses, specifically:

Semigroup allows combining values inside both Failure and Success but this requires both values to implement the Semigroup instance. This doesn't fit our goal, since Password can't have a reasonble Semigroup instance.

Alternative returns first Success or combines all Failures. We can notice that Alternative also doesn't work for us here.

In our case we are interested in collecting all possible errors and returning Success only when all checks are passed. Fortunately, Applicative is exactly what we need here. So we can use the *> operator to compose all checks for password:

>>> :{
validatePassword :: String -> Validation (NonEmpty FormValidationError) Password
validatePassword password =
    validateShortPassword password *> validatePasswordDigit password
:}

Let's see how it works:

>>> validatePassword "abcd"
Failure (ShortPassword :| [NoDigitPassword])
>>> validatePassword "abcd1"
Failure (ShortPassword :| [])
>>> validatePassword "abcd12345"
Success "abcd12345"

The validation library provides several convenient combinators, so you can write the password check in a shorter way:

validatePassword :: String -> Validation (NonEmpty FormValidationError) Password
validatePassword = fmap Password . validateAll
    [ (`failureIf`     ShortPassword)   . (< 8) . length
    , (`failureUnless` NoDigitPassword) . any isDigit
    ]

After we've implemented validations for all fields, we can compose them together to produce validation for the whole User. As before, we are going to use the Applicative instance:

>>> :{
validateForm :: Form -> Validation (NonEmpty FormValidationError) User
validateForm Form{..} = User
    <$> validateName formUserName
    <*> validatePassword formPassword
:}

And it works like a charm:

>>> validateForm (Form "" "")
Failure (EmptyName :| [ShortPassword,NoDigitPassword])
>>> validateForm (Form "John" "abc")
Failure (ShortPassword :| [NoDigitPassword])
>>> validateForm (Form "Jonh" "qwertypassword")
Failure (NoDigitPassword :| [])
>>> validateForm (Form "Jonh" "qwertypassword123")
Success (User {userName = "Jonh", userPassword = "qwertypassword123"})

Interface functions

isFailure :: Validation e a -> Bool Source #

Predicate on if the given Validation is Failure.

>>> isFailure (Failure 'e')
True
>>> isFailure (Success 'a')
False

isSuccess :: Validation e a -> Bool Source #

Predicate on if the given Validation is Success.

>>> isSuccess (Success 'a')
True
>>> isSuccess (Failure 'e')
False

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

Transforms the value of the given Validation into x using provided functions that can transform Failure and Success value into the resulting type respectively.

>>> let myValidation = validation (<> " world!") (show . (* 10))
>>> myValidation (Success 100)
"1000"
>>> myValidation (Failure "Hello")
"Hello world!"

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

Filters out all Failure values into the new list of es from the given list of Validations.

Note that the order is preserved.

>>> failures [Failure "Hello", Success 1, Failure "world", Success 2, Failure "!" ]
["Hello","world","!"]

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

Filters out all Success values into the new list of as from the given list of Validations.

Note that the order is preserved.

>>> successes [Failure "Hello", Success 1, Failure "world", Success 2, Failure "!" ]
[1,2]

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

Redistributes the given list of Validations into two lists of es and es, where the first list contains all values of Failures and the second one — Successes correspondingly.

Note that the order is preserved.

>>> partitionValidations [Failure "Hello", Success 1, Failure "world", Success 2, Failure "!" ]
(["Hello","world","!"],[1,2])

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

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

>>> fromFailure "default" (Failure "failure")
"failure"
>>> fromFailure "default" (Success 1)
"default"

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

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

>>> fromSuccess 42 (Success 1)
1
>>> fromSuccess 42 (Failure "failure")
42

NonEmpty combinators

When using Validation, we often work with the NonEmpty list of errors, and those lists will be concatenated later.

The following functions aim to help with writing more concise code.

For example, instead of (perfectly fine) code like:

>>> :{
validateNameVerbose :: String -> Validation (NonEmpty String) String
validateNameVerbose name
    | null name = Failure ("Empty Name" :| [])
    | otherwise = Success name
:}

one can write simply:

>>> :{
validateNameSimple :: String -> Validation (NonEmpty String) String
validateNameSimple name = name <$ failureIf (null name) "Empty Name"
:}

failure :: e -> Validation (NonEmpty e) a Source #

Create a Failure of NonEmpty list with a single given error.

>>> failure "I am a failure"
Failure ("I am a failure" :| [])

failureIf :: Bool -> e -> Validation (NonEmpty e) () Source #

Returns a Failure in case of the given predicate is True. Returns Success () otherwise.

>>> let shouldFail = (==) "I am a failure"
>>> failureIf (shouldFail "I am a failure") "I told you so"
Failure ("I told you so" :| [])
>>> failureIf (shouldFail "I am NOT a failure") "okay"
Success ()

failureUnless :: Bool -> e -> Validation (NonEmpty e) () Source #

Returns a Failure unless the given predicate is True. Returns Success () in case of the predicate is satisfied.

Similar to failureIf with the reversed predicate.

failureUnless p ≡ failureIf (not p)
>>> let shouldFail = (==) "I am a failure"
>>> failureUnless (shouldFail "I am a failure") "doesn't matter"
Success ()
>>> failureUnless (shouldFail "I am NOT a failure") "I told you so"
Failure ("I told you so" :| [])

Either conversion

Validation is usually compared to the Either data type due to the similarity in structure, nature and use case. Here is a quick table you can relate to, in order to see the main properties and differences between these two data types:

EitherValidation
Error resultLeftFailure
Successful resultRightSuccess
Applicative instanceStops on the first LeftAggregates all Failures
Monad instanceLawful instanceCannot exist

Comparison in example

For the sake of better illustration of the difference between Either and Validation, let's go through the example of how parsing is done with the usage of these types.

Our goal is to parse two given Strings and return their sum in case if both of them are valid Ints. If any of the inputs is failing to be parsed we should return the ParseError which we are introducing right now:

>>> :{
newtype ParseError = ParseError
    { nonParsedString :: String
    } deriving stock (Show)
:}

Let's first implement the parsing of single input in the Either context:

>>> :{
parseEither :: String -> Either ParseError Int
parseEither input = case readMaybe @Int input of
    Just x  -> Right x
    Nothing -> Left $ ParseError input
:}

And the final function for Either looks like this:

>>> :{
parseSumEither :: String -> String -> Either ParseError Int
parseSumEither str1 str2 = do
    let x = parseEither str1
    let y = parseEither str2
    liftA2 (+) x y
:}

Let's now test it in action.

>>> parseSumEither "1" "2"
Right 3
>>> parseSumEither "NaN" "42"
Left (ParseError {nonParsedString = "NaN"})
>>> parseSumEither "15" "Infinity"
Left (ParseError {nonParsedString = "Infinity"})
>>> parseSumEither "NaN" "infinity"
Left (ParseError {nonParsedString = "NaN"})

Note how in the case of both failed parsing we got only the first NaN.

To finish our comparison, let's implement the same functionality using Validation properties.

>>> :{
parseValidation :: String -> Validation (NonEmpty ParseError) Int
parseValidation input = case readMaybe @Int input of
    Just x  -> Success x
    Nothing -> failure $ ParseError input
:}
>>> :{
parseSumValidation :: String -> String -> Validation (NonEmpty ParseError) Int
parseSumValidation str1 str2 = do
    let x = parseValidation str1
    let y = parseValidation str2
    liftA2 (+) x y
:}

It looks almost completely identical except for the resulting type — Validation (NonEmpty ParseError) Int. But let's see if they behave the same way:

>>> parseSumValidation "1" "2"
Success 3
>>> parseSumValidation "NaN" "42"
Failure (ParseError {nonParsedString = "NaN"} :| [])
>>> parseSumValidation "15" "infinity"
Failure (ParseError {nonParsedString = "infinity"} :| [])
>>> parseSumValidation "NaN" "infinity"
Failure (ParseError {nonParsedString = "NaN"} :| [ParseError {nonParsedString = "infinity"}])

As expected, with Validation we got all parse Failures we received on the way.

Combinators

We are providing several functions for better integration with the Either related code in this section.

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

Transform a Validation into an Either.

>>> validationToEither (Success "whoop")
Right "whoop"
>>> validationToEither (Failure "nahh")
Left "nahh"

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

Transform an Either into a Validation.

>>> eitherToValidation (Right "whoop")
Success "whoop"
>>> eitherToValidation (Left "nahh")
Failure "nahh"

Combinators

validateAll :: forall e b a f. (Foldable f, Semigroup e) => f (a -> Validation e b) -> a -> Validation e a Source #

Validate all given checks in a Foldable. Returns the Success of the start element when all checks are successful.

A basic example of usage could look like this:

> let validatePassword = validateAll
        [ validateEmptyPassword
        , validateShortPassword
        ]

> validateAll "VeryStrongPassword"
Success "VeryStrongPassword"

> validateAll ""
Failure (EmptyPassword :| [ShortPassword])

When* functions

whenSuccess :: Applicative f => x -> Validation e a -> (a -> f x) -> f x Source #

Applies the given action to Validation if it is Success and returns the result. In case of Failure the default value is returned.

>>> whenSuccess "bar" (Failure "foo") (\a -> "success!" <$ print a)
"bar"
>>> whenSuccess "bar" (Success 42) (\a -> "success!" <$ print a)
42
"success!"

whenFailure :: Applicative f => x -> Validation e a -> (e -> f x) -> f x Source #

Applies the given action to Validation if it is Failure and returns the result. In case of Success the default value is returned.

>>> whenFailure "bar" (Failure 42) (\a -> "foo" <$ print a)
42
"foo"
>>> whenFailure "bar" (Success 42) (\a -> "foo" <$ print a)
"bar"

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

Applies given action to the Validation content if it is Success.

Similar to whenSuccess but the default value is ().

>>> whenSuccess_ (Failure "foo") print
>>> whenSuccess_ (Success 42) print
42

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

Applies given action to the Validation content if it is Failure.

Similar to whenFailure but the default value is ().

>>> whenFailure_ (Success 42) putStrLn
>>> whenFailure_ (Failure "foo") putStrLn
foo

whenSuccessM :: Monad m => x -> m (Validation e a) -> (a -> m x) -> m x Source #

Monadic version of whenSuccess. Applies monadic action to the given Validation in case of Success. Returns the resulting value, or provided default.

>>> whenSuccessM "bar" (pure $ Failure "foo") (\a -> "success!" <$ print a)
"bar"
>>> whenSuccessM "bar" (pure $ Success 42) (\a -> "success!" <$ print a)
42
"success!"

whenFailureM :: Monad m => x -> m (Validation e a) -> (e -> m x) -> m x Source #

Monadic version of whenFailure. Applies monadic action to the given Validation in case of Failure. Returns the resulting value, or provided default.

>>> whenFailureM "bar" (pure $ Failure 42) (\a -> "foo" <$ print a)
42
"foo"
>>> whenFailureM "bar" (pure $ Success 42) (\a -> "foo" <$ print a)
"bar"

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

Monadic version of whenSuccess_. Applies monadic action to the given Validation in case of Success. Similar to whenSuccessM but the default is ().

>>> whenSuccessM_ (pure $ Failure "foo") print
>>> whenSuccessM_ (pure $ Success 42) print
42

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

Monadic version of whenFailure_. Applies monadic action to the given Validation in case of Failure. Similar to whenFailureM but the default is ().

>>> whenFailureM_ (pure $ Success 42) putStrLn
>>> whenFailureM_ (pure $ Failure "foo") putStrLn
foo

Maybe conversion

failureToMaybe :: Validation e a -> Maybe e Source #

Maps Failure of Validation to Just.

>>> failureToMaybe (Failure True)
Just True
>>> failureToMaybe (Success "aba")
Nothing

successToMaybe :: Validation e a -> Maybe a Source #

Maps Success of Validation to Just.

>>> successToMaybe (Failure True)
Nothing
>>> successToMaybe (Success "aba")
Just "aba"

maybeToFailure :: a -> Maybe e -> Validation e a Source #

Maps Just to Failure In case of Nothing it wraps the given default value into Success.

>>> maybeToFailure True (Just "aba")
Failure "aba"
>>> maybeToFailure True Nothing
Success True

maybeToSuccess :: e -> Maybe a -> Validation e a Source #

Maps Just to Success. In case of Nothing it wraps the given default value into Failure

>>> maybeToSuccess True (Just "aba")
Success "aba"
>>> maybeToSuccess True Nothing
Failure True