Copyright | (c) TotallyNotChase 2021 |
---|---|
License | MIT |
Maintainer | totallynotchase42@gmail.com |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module is re-exported by Valida. You probably don't need to import this.
This module exports the primitive, as well as utility, ValidationRule
combinators.
As well as the orElse
, andAlso
, satisfyAny
, and satisfyAll
functions, and some more utilities.
Synopsis
- failureIf :: (a -> Bool) -> e -> ValidationRule (NonEmpty e) a
- failureUnless :: (a -> Bool) -> e -> ValidationRule (NonEmpty e) a
- failureIf' :: (a -> Bool) -> ValidationRule () a
- failureUnless' :: (a -> Bool) -> ValidationRule () a
- negateRule :: e -> ValidationRule e1 a -> ValidationRule e a
- negateRule' :: ValidationRule e a -> ValidationRule () a
- andAlso :: ValidationRule e a -> ValidationRule e a -> ValidationRule e a
- falseRule :: Monoid e => ValidationRule e a
- orElse :: Semigroup e => ValidationRule e a -> ValidationRule e a -> ValidationRule e a
- satisfyAll :: Foldable t => t (ValidationRule e a) -> ValidationRule e a
- satisfyAny :: (Foldable t, Semigroup e) => t (ValidationRule e a) -> ValidationRule e a
- (</>) :: Semigroup e => ValidationRule e a -> ValidationRule e a -> ValidationRule e a
- atleastContains :: Foldable t => (a -> Bool) -> e -> ValidationRule (NonEmpty e) (t a)
- lengthAbove :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a)
- lengthBelow :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a)
- lengthWithin :: Foldable t => (Int, Int) -> e -> ValidationRule (NonEmpty e) (t a)
- maxLengthOf :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a)
- maxValueOf :: Ord a => a -> e -> ValidationRule (NonEmpty e) a
- minLengthOf :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a)
- minValueOf :: Ord a => a -> e -> ValidationRule (NonEmpty e) a
- mustBe :: Eq a => a -> e -> ValidationRule (NonEmpty e) a
- mustContain :: (Foldable t, Eq a) => a -> e -> ValidationRule (NonEmpty e) (t a)
- notEmpty :: Foldable t => e -> ValidationRule (NonEmpty e) (t a)
- ofLength :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a)
- onlyContains :: Foldable t => (a -> Bool) -> e -> ValidationRule (NonEmpty e) (t a)
- valueAbove :: Ord a => a -> e -> ValidationRule (NonEmpty e) a
- valueBelow :: Ord a => a -> e -> ValidationRule (NonEmpty e) a
- valueWithin :: Ord a => (a, a) -> e -> ValidationRule (NonEmpty e) a
- atleastContains' :: Foldable t => (a -> Bool) -> ValidationRule () (t a)
- lengthAbove' :: Foldable t => Int -> ValidationRule () (t a)
- lengthBelow' :: Foldable t => Int -> ValidationRule () (t a)
- lengthWithin' :: Foldable t => (Int, Int) -> ValidationRule () (t a)
- maxLengthOf' :: Foldable t => Int -> ValidationRule () (t a)
- maxValueOf' :: Ord a => a -> ValidationRule () a
- minLengthOf' :: Foldable t => Int -> ValidationRule () (t a)
- minValueOf' :: Ord a => a -> ValidationRule () a
- mustBe' :: Eq a => a -> ValidationRule () a
- mustContain' :: (Foldable t, Eq a) => a -> ValidationRule () (t a)
- notEmpty' :: Foldable t => ValidationRule () (t a)
- ofLength' :: Foldable t => Int -> ValidationRule () (t a)
- onlyContains' :: Foldable t => (a -> Bool) -> ValidationRule () (t a)
- valueAbove' :: Ord a => a -> ValidationRule () a
- valueBelow' :: Ord a => a -> ValidationRule () a
- valueWithin' :: Ord a => (a, a) -> ValidationRule () a
- optionally :: ValidationRule e a -> ValidationRule e (Maybe a)
Primitive NonEmpty
combinators
failureIf :: (a -> Bool) -> e -> ValidationRule (NonEmpty e) a Source #
Build a rule that fails with given error if the given predicate succeeds.
failureIf predc =failureUnless
(not
. predc)
Examples
>>>
runValidator (validate (failureIf (>0) "Positive")) 5
Failure ("Positive" :| [])>>>
runValidator (validate (failureIf (>0) "Positive")) 0
Success 0>>>
runValidator (validate (failureIf (>0) "Positive")) (-1)
Success (-1)
failureUnless :: (a -> Bool) -> e -> ValidationRule (NonEmpty e) a Source #
Build a rule that fails with given error unless the given predicate succeeds.
failureUnless predc =failureIf
(not
. predc)
Examples
>>>
runValidator (validate (failureUnless (>0) "NonPositive")) 5
Success 5>>>
runValidator (validate (failureUnless (>0) "NonPositive")) 0
Failure ("NonPositive" :| [])>>>
runValidator (validate (failureUnless (>0) "NonPositive")) (-1)
Failure ("NonPositive" :| [])
Primitive Unit combinators
failureIf' :: (a -> Bool) -> ValidationRule () a Source #
Like failureIf
but uses Unit as the ValidationRule
error type.
failureIf' predc =failureUnless'
(not
. predc)
label (const
(err :| [])) (failureIf' predc) =failureIf
predc err
Examples
>>>
runValidator (validate (failureIf' (>0))) 5
Failure ()>>>
runValidator (validate (failureIf' (>0))) 0
Success 0>>>
runValidator (validate (failureIf' (>0))) (-1)
Success (-1)
failureUnless' :: (a -> Bool) -> ValidationRule () a Source #
Like failureUnless
but uses Unit as the ValidationRule
error type.
failureUnless' predc =failureIf'
(not
. predc)
label (const
(err :| [])) (failureUnless' predc) =failureUnless
predc err
Examples
>>>
runValidator (validate (failureUnless' (>0))) 5
Success 5>>>
runValidator (validate (failureUnless' (>0))) 0
Failure ()>>>
runValidator (validate (failureUnless' (>0))) (-1)
Failure ()
Negating ValidationRule
negateRule :: e -> ValidationRule e1 a -> ValidationRule e a Source #
Build a rule that succeeds if given rule fails and vice versa.
Examples
>>>
let rule = negateRule "NonPositive" (failureIf (>0) "Positive")
>>>
runValidator (validate rule) 5
Success 5>>>
runValidator (validate rule) 0
Failure "NonPositive">>>
runValidator (validate rule) (-1)
Failure "NonPositive"
negateRule' :: ValidationRule e a -> ValidationRule () a Source #
Like negateRule
but uses Unit as the ValidationRule
error type.
Combining ValidationRule
s
andAlso :: ValidationRule e a -> ValidationRule e a -> ValidationRule e a Source #
Build a rule that only succeeds if both of the given rules succeed. The very first failure is yielded.
This is the same as the semigroup operation (i.e (<>)
) on ValidationRule
.
rule1 `andAlso` (rule2 `andAlso` rule3) = (rule1 `andAlso` rule2) `andAlso` rule3
mempty
`andAlso` rule = rule
rule `andAlso` mempty
= rule
Examples
>>>
let rule = failureIf (>0) "Positive" `andAlso` failureIf even "Even"
>>>
runValidator (validate rule) 5
Failure ("Positive" :| [])>>>
runValidator (validate rule) (-2)
Failure ("Even" :| [])>>>
runValidator (validate rule) (-1)
Success (-1)
falseRule :: Monoid e => ValidationRule e a Source #
A ValidationRule
that always fails with supplied error. This is the identity of orElse
(i.e (</>)
).
falseRule `orElse
` rule = rule
rule `orElse
` falseRule = rule
Examples
>>>
runValidator (validate falseRule) 42
Failure ()
orElse :: Semigroup e => ValidationRule e a -> ValidationRule e a -> ValidationRule e a Source #
Build a rule that succeeds if either of the given rules succeed. If both fail, the errors are combined.
rule1 `orElse` (rule2 `orElse` rule3) = (rule1 `orElse` rule2) `orElse` rule3
falseRule
e `orElse` rule = rule
rule `orElse` falseRule
e = rule
Examples
>>>
let rule = failureIf (>0) "Positive" `orElse` failureIf even "Even"
>>>
runValidator (validate rule) 5
Success 5>>>
runValidator (validate rule) 4
Failure ("Positive" :| ["Even"])>>>
runValidator (validate rule) 0
Success 0>>>
runValidator (validate rule) (-1)
Success (-1)
satisfyAll :: Foldable t => t (ValidationRule e a) -> ValidationRule e a Source #
satisfyAny :: (Foldable t, Semigroup e) => t (ValidationRule e a) -> ValidationRule e a Source #
(</>) :: Semigroup e => ValidationRule e a -> ValidationRule e a -> ValidationRule e a infixr 5 Source #
A synonym for orElse
. Satisfies associativity law and hence forms a semigroup.
Common derivates of primitive NonEmpty
combinators
atleastContains :: Foldable t => (a -> Bool) -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build an any
rule.
atleastContains x =failureUnless
(any
x)
lengthAbove :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build a minimum length (inclusive) rule.
lengthAbove x = minLengthOf
(x + 1)
lengthAbove x =failureUnless
((>n) .length
)
lengthBelow :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build a maximum length (inclusive) rule.
lengthBelow x = maxLengthOf
(x - 1)
lengthBelow x =failureUnless
((<n) .length
)
lengthWithin :: Foldable t => (Int, Int) -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build an inRange
rule for length.
lengthWithin (min, max) =minLengthOf
min `andAlso
`maxLengthOf
max
lengthWithin r =failureUnless
(inRange
r .length
)
maxLengthOf :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build a maximum length (inclusive) rule.
maxLengthOf n =failureUnless
((<=n) .length
)
maxValueOf :: Ord a => a -> e -> ValidationRule (NonEmpty e) a Source #
Build a maximum value (inclusive) rule.
maxValueOf x = failureUnless
(<=x)
minLengthOf :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build a minimum length (inclusive) rule.
minLengthOf x =failureUnless
((>=n) .length
)
minValueOf :: Ord a => a -> e -> ValidationRule (NonEmpty e) a Source #
Build a minimum value (inclusive) rule.
minValueOf x = failureUnless
(>=x)
mustBe :: Eq a => a -> e -> ValidationRule (NonEmpty e) a Source #
Build an equality rule for value.
mustBe x = failureUnless
(==x)
mustContain :: (Foldable t, Eq a) => a -> e -> ValidationRule (NonEmpty e) (t a) Source #
ofLength :: Foldable t => Int -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build an equality rule for length.
ofLength x =failureUnless
((==x) .length
)
onlyContains :: Foldable t => (a -> Bool) -> e -> ValidationRule (NonEmpty e) (t a) Source #
Build an all
rule.
onlyContains x =failureUnless
(all
x)
valueAbove :: Ord a => a -> e -> ValidationRule (NonEmpty e) a Source #
Build a minimum value (exclusive) rule.
valueAbove x = minValueOf
(x + 1)
valueAbove x = failureUnless
(>x)
valueBelow :: Ord a => a -> e -> ValidationRule (NonEmpty e) a Source #
Build a maximum value (exclusive) rule.
valueBelow x = minValueOf
(x - 1)
valueBelow x = failureUnless
(<x)
valueWithin :: Ord a => (a, a) -> e -> ValidationRule (NonEmpty e) a Source #
Build an inRange
rule for value.
valueWithin (m, n) =minValueOf
m `andAlso
`maxValueOf
n
valueWithin (m, n) = failureUnless
(x -> m <= x && x <= n)
Common derivates of primitive Unit combinators
atleastContains' :: Foldable t => (a -> Bool) -> ValidationRule () (t a) Source #
Like atleastContains
but uses Unit as the ValidationRule
error type.
lengthAbove' :: Foldable t => Int -> ValidationRule () (t a) Source #
Like lengthAbove
but uses Unit as the ValidationRule
error type.
lengthBelow' :: Foldable t => Int -> ValidationRule () (t a) Source #
Like lengthBelow
but uses Unit as the ValidationRule
error type.
lengthWithin' :: Foldable t => (Int, Int) -> ValidationRule () (t a) Source #
Like lengthWithin
but uses Unit as the ValidationRule
error type.
maxLengthOf' :: Foldable t => Int -> ValidationRule () (t a) Source #
Like maxLengthOf
but uses Unit as the ValidationRule
error type.
maxValueOf' :: Ord a => a -> ValidationRule () a Source #
Like maxValueOf
but uses Unit as the ValidationRule
error type.
minLengthOf' :: Foldable t => Int -> ValidationRule () (t a) Source #
Like minLengthOf
but uses Unit as the ValidationRule
error type.
minValueOf' :: Ord a => a -> ValidationRule () a Source #
Like minValueOf
but uses Unit as the ValidationRule
error type.
mustBe' :: Eq a => a -> ValidationRule () a Source #
Like mustBe
but uses Unit as the ValidationRule
error type.
mustContain' :: (Foldable t, Eq a) => a -> ValidationRule () (t a) Source #
Like mustContain
but uses Unit as the ValidationRule
error type.
notEmpty' :: Foldable t => ValidationRule () (t a) Source #
Like notEmpty
but uses Unit as the ValidationRule
error type.
ofLength' :: Foldable t => Int -> ValidationRule () (t a) Source #
Like ofLength
but uses Unit as the ValidationRule
error type.
onlyContains' :: Foldable t => (a -> Bool) -> ValidationRule () (t a) Source #
Like onlyContains
but uses Unit as the ValidationRule
error type.
valueAbove' :: Ord a => a -> ValidationRule () a Source #
Like valueAbove
but uses Unit as the ValidationRule
error type.
valueBelow' :: Ord a => a -> ValidationRule () a Source #
Like valueBelow
but uses Unit as the ValidationRule
error type.
valueWithin' :: Ord a => (a, a) -> ValidationRule () a Source #
Like valueWithin
but uses Unit as the ValidationRule
error type.
Type specific ValidationRule
s
optionally :: ValidationRule e a -> ValidationRule e (Maybe a) Source #
Build a rule that runs given rule only if input is Just
.
Yields Success
when input is Nothing
.
Examples
>>>
runValidator (validate (optionally (failureIf even "Even"))) (Just 5)
Success (Just 5)>>>
runValidator (validate (optionally (failureIf even "Even"))) (Just 6)
Failure ("Even" :| [])>>>
runValidator (validate (optionally (failureIf even "Even"))) Nothing
Success Nothing