validators-0.0.1: Composable validations for your Haskell data types

Safe HaskellSafe
LanguageHaskell2010

Data.Validator

Description

This module defines the Validator data type and helper functions for creating various validators.

Synopsis

Documentation

data Validator err subject Source #

Datatype for checking if a validation holds for a subject.

  • subject can be any data type for which assertions need to be checked.
  • err can be any type representing an error, but it will only be possible to combine validators if the error type has a Semigroup instance.

Execute a validator by passing it to the validate function.

A Validator is both a Semigroup and a Monoid, making it possible to combine smaller validators into larger validators. A combined validator will accumulate errors from all of it's sub-validators.

Instances
Contravariant (Validator err) Source # 
Instance details

Defined in Data.Validator

Methods

contramap :: (a -> b) -> Validator err b -> Validator err a #

(>$) :: b -> Validator err b -> Validator err a #

Semigroup err => Semigroup (Validator err subject) Source # 
Instance details

Defined in Data.Validator

Methods

(<>) :: Validator err subject -> Validator err subject -> Validator err subject #

sconcat :: NonEmpty (Validator err subject) -> Validator err subject #

stimes :: Integral b => b -> Validator err subject -> Validator err subject #

Monoid err => Monoid (Validator err subject) Source # 
Instance details

Defined in Data.Validator

Methods

mempty :: Validator err subject #

mappend :: Validator err subject -> Validator err subject -> Validator err subject #

mconcat :: [Validator err subject] -> Validator err subject #

validate :: Validator err subject -> subject -> Validation err subject Source #

Runs a validator on a subject.

The result is a Validation containing all accumulated errors, or the subject wrapped in a Success value.

assert :: (subject -> Bool) -> err -> Validator err subject Source #

Creates a validator that will return an error if the given predicate doesn't hold.

Since any predicate can be provided for checking if the subject satisfies certain conditions, this can be used to build your own custom validators.

Usage:

>>> let validator = assert (> 10) ["too small"]
>>> validate validator 11
Success 11
>>> validate validator 1
Failure ["too small"]

refute :: (subject -> Bool) -> err -> Validator err subject Source #

Creates a validator that will return an error if the given predicate holds.

Since any predicate can be provided for checking if the subject satisfies certain conditions, this can be used to build your own custom validators.

Usage:

>>> let validator = refute (> 10) ["too big"]
>>> validate validator 11
Failure ["too big"]
>>> validate validator 1
Success 1

ifNothing :: err -> Validator err (Maybe a) Source #

Returns an error if a Maybe is Nothing.

Usage:

>>> let validator = ifNothing ["Found nothing."]
>>> validate validator Nothing
Failure ["Found nothing."]
>>> validate validator (Just "Bob")
Success (Just "Bob")

ifLeft :: err -> Validator err (Either a b) Source #

Returns an error if an Either contains a Left.

Usage:

>>> let validator = ifLeft ["Found left."]
>>> validate validator (Left 123)
Failure ["Found left."]
>>> validate validator (Right 456)
Success (Right 456)

class HasSize a where Source #

Helper typeclass for checking if a value is empty.

Minimal complete definition

size

Methods

size :: a -> Int Source #

isEmpty :: a -> Bool Source #

Instances
HasSize [a] Source # 
Instance details

Defined in Data.Validator

Methods

size :: [a] -> Int Source #

isEmpty :: [a] -> Bool Source #

HasSize (Seq a) Source # 
Instance details

Defined in Data.Validator

Methods

size :: Seq a -> Int Source #

isEmpty :: Seq a -> Bool Source #

HasSize (Set a) Source # 
Instance details

Defined in Data.Validator

Methods

size :: Set a -> Int Source #

isEmpty :: Set a -> Bool Source #

HasSize (Map k v) Source # 
Instance details

Defined in Data.Validator

Methods

size :: Map k v -> Int Source #

isEmpty :: Map k v -> Bool Source #

ifEmpty :: HasSize subject => err -> Validator err subject Source #

Returns an error if the function returns an "empty" value.

Usage:

>>> let validator = ifEmpty ["Empty."]
>>> validate validator []
Failure ["Empty."]
>>> validate validator [1, 2, 3]
Success [1,2,3]
>>> validate validator (Map.fromList [('a', 1), ('b', 2)])
Success (fromList [('a',1),('b',2)])

minSize :: HasSize subject => Int -> err -> Validator err subject Source #

Returns an error if the value has a size smaller than required.

Usage:

>>> let validator = minSize 3 ["Too small."]
>>> validate validator []
Failure ["Too small."]
>>> validate validator [1, 2]
Failure ["Too small."]
>>> validate validator [1, 2, 3]
Success [1,2,3]

maxSize :: HasSize subject => Int -> err -> Validator err subject Source #

Returns an error if the value has a size smaller than required.

Usage:

>>> let validator = maxSize 3 ["Too big."]
>>> validate validator [1, 2, 3, 4]
Failure ["Too big."]
>>> validate validator [1, 2, 3]
Success [1,2,3]

class IsOnlyWhiteSpace a where Source #

Helper typeclass for checking if a value contains only whitespace characters.

Methods

isOnlyWhiteSpace :: a -> Bool Source #

Instances
IsOnlyWhiteSpace String Source # 
Instance details

Defined in Data.Validator

IsOnlyWhiteSpace Text Source # 
Instance details

Defined in Data.Validator

IsOnlyWhiteSpace Text Source # 
Instance details

Defined in Data.Validator

ifBlank :: IsOnlyWhiteSpace subject => err -> Validator err subject Source #

Returns an error if the function returns a value containing only whitespace.

Usage:

>>> let validator = ifBlank ["Only whitespace."]
>>> validate validator "   \t \n \r "
Failure ["Only whitespace."]
>>> validate validator "not empty"
Success "not empty"