| Copyright | (c) 2014 Chris Allen Edward Kmett (c) 2018-2019 Kowainik | 
|---|---|
| License | MIT | 
| Maintainer | Kowainik <xrom.xkov@gmail.com> | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Relude.Extra.Validation
Contents
Description
Validation is a monoidal sibling to Either but Validation doesn't have a
Monad instance. 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:
- Validating each input of a form with multiple inputs.
- Performing multiple validations of a single value.
Instances of different standard typeclasses provide various semantics:
- Functor: change the type inside- Success.
- Bifunctor: change both- Failureand- Success.
- Applicative: apply function to values inside- Successand accumulate errors inside- Failure.
- Semigroup: accumulate both- Failureand- Successwith- <>.
- Monoid:- Successthat shores- mempty.
- Alternative: return first- Successor accumulate all errors inside- Failure.
Synopsis
- data Validation e a
- validationToEither :: Validation e a -> Either e a
- eitherToValidation :: Either e a -> Validation e a
How to use
Take for example a type Computer that needs to be validated:
>>>:{data Computer = Computer { computerRam :: !Int -- ^ Ram in Gigabytes , computerCpus :: !Int } deriving (Eq, Show) :}
You can validate that the computer has a minimum of 16GB of RAM:
>>>:{validateRam :: Int -> Validation [Text] Int validateRam ram | ram >= 16 = Success ram | otherwise = Failure ["Not enough RAM"] :}
and that the processor has at least two CPUs:
>>>:{validateCpus :: Int -> Validation [Text] Int validateCpus cpus | cpus >= 2 = Success cpus | otherwise = Failure ["Not enough CPUs"] :}
You can use these functions with the Applicative instance of the Validation
type to construct a validated Computer. You will get either (pun intended) a
valid Computer or the errors that prevent it from being considered valid.
Like so:
>>>:{mkComputer :: Int -> Int -> Validation [Text] Computer mkComputer ram cpus = Computer <$> validateRam ram <*> validateCpus cpus :}
Using mkComputer we get a Success Computer or a list with all possible errors:
>>>mkComputer 16 2Success (Computer {computerRam = 16, computerCpus = 2})
>>>mkComputer 16 1Failure ["Not enough CPUs"]
>>>mkComputer 15 2Failure ["Not enough RAM"]
>>>mkComputer 15 1Failure ["Not enough RAM","Not enough CPUs"]
data Validation e a Source #
Validation is Either with a Left that is a Semigroup.
Instances
| Bitraversable Validation Source # | |
| Defined in Relude.Extra.Validation Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Validation a b -> f (Validation c d) # | |
| Bifoldable Validation Source # | |
| Defined in Relude.Extra.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 # | |
| Defined in Relude.Extra.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 # | |
| (NoValidationMonadError, Semigroup e) => Monad (Validation e) Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. It's not possible to implement lawful  In case it is used by mistake, the user will see the following: 
 Since: 0.6.0.0 | 
| Defined in Relude.Extra.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 # | |
| Defined in Relude.Extra.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 if the most important instance for the  Examples 
 
 
 
 
 
 
 Implementations of all functions are lazy and they correctly work if some arguments are not fully evaluated. 
 
 | 
| Defined in Relude.Extra.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 # | |
| Defined in Relude.Extra.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 # | |
| Defined in Relude.Extra.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 following behavior for the binary operator: 
 Examples 
 
 | 
| Defined in Relude.Extra.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] # | |
| (Eq e, Eq a) => Eq (Validation e a) Source # | |
| Defined in Relude.Extra.Validation Methods (==) :: Validation e a -> Validation e a -> Bool # (/=) :: Validation e a -> Validation e a -> Bool # | |
| (Ord e, Ord a) => Ord (Validation e a) Source # | |
| Defined in Relude.Extra.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 # | |
| Defined in Relude.Extra.Validation Methods showsPrec :: Int -> Validation e a -> ShowS # show :: Validation e a -> String # showList :: [Validation e a] -> ShowS # | |
| (Semigroup e, Semigroup a) => Semigroup (Validation e a) Source # | This instances covers the following cases: 
 Examples 
 
 
 
 Since: 0.6.0.0 | 
| Defined in Relude.Extra.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, Monoid a) => Monoid (Validation e a) Source # | Since: 0.6.0.0 | 
| Defined in Relude.Extra.Validation Methods mempty :: Validation e a # mappend :: Validation e a -> Validation e a -> Validation e a # mconcat :: [Validation e a] -> Validation e a # | |
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"