Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type ValidationM e = ValidationT e Identity
- data ValidationT e m a
- type ValidationRule e a = ValidationRuleT e Identity a
- type ValidationRuleT e m a = TransValidationRuleT e m a a
- type TransValidationRule e a b = TransValidationRuleT e Identity a b
- type TransValidationRuleT e m a b = a -> ValidationT e m b
- runValidator :: TransValidationRule e a b -> a -> Either e b
- runValidatorT :: Monad m => TransValidationRuleT e m a b -> a -> m (Either e b)
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- minLength :: (Monad m, HasLength a) => Int64 -> e -> ValidationRuleT e m a
- maxLength :: (Monad m, HasLength a) => Int64 -> e -> ValidationRuleT e m a
- lengthBetween :: (Monad m, HasLength a) => Int64 -> Int64 -> e -> ValidationRuleT e m a
- notEmpty :: (Monad m, HasLength a) => e -> ValidationRuleT e m a
- largerThan :: (Monad m, Ord a) => a -> e -> ValidationRuleT e m a
- smallerThan :: (Monad m, Ord a) => a -> e -> ValidationRuleT e m a
- valueBetween :: (Monad m, Ord a) => a -> a -> e -> ValidationRuleT e m a
- matchesRegex :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, Monad m) => Regex -> e -> ValidationRuleT e m a
- conformsPred :: Monad m => (a -> Bool) -> e -> ValidationRuleT e m a
- conformsPredM :: Monad m => (a -> m Bool) -> e -> ValidationRuleT e m a
- requiredValue :: Monad m => e -> TransValidationRuleT e m (Maybe a) a
- nonEmptyList :: Monad m => e -> TransValidationRuleT e m [a] (NonEmpty a)
- conformsPredTrans :: Monad m => (a -> Maybe b) -> e -> TransValidationRuleT e m a b
- conformsPredTransM :: Monad m => (a -> m (Maybe b)) -> e -> TransValidationRuleT e m a b
- class HasLength a where
- class ConvertibleStrings a b where
- convertString :: a -> b
- data Int64
- re :: QuasiQuoter
- mkRegexQQ :: [PCREOption] -> QuasiQuoter
- data Regex
Core monad and runners
type ValidationM e = ValidationT e Identity Source #
The validation monad
data ValidationT e m a Source #
The validation monad transformer
Instances
type ValidationRule e a = ValidationRuleT e Identity a Source #
type ValidationRuleT e m a = TransValidationRuleT e m a a Source #
type TransValidationRule e a b = TransValidationRuleT e Identity a b Source #
type TransValidationRuleT e m a b = a -> ValidationT e m b Source #
runValidator :: TransValidationRule e a b -> a -> Either e b Source #
Run a validation on a type a
runValidatorT :: Monad m => TransValidationRuleT e m a b -> a -> m (Either e b) Source #
Run a validation on a type a
Combinators
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
'(bs
' can be understood as the >=>
cs) ado
expression
do b <- bs a cs b
Checks
minLength :: (Monad m, HasLength a) => Int64 -> e -> ValidationRuleT e m a Source #
Check that the value is at least N elements long
maxLength :: (Monad m, HasLength a) => Int64 -> e -> ValidationRuleT e m a Source #
Check that the value is at maxium N elements long
lengthBetween :: (Monad m, HasLength a) => Int64 -> Int64 -> e -> ValidationRuleT e m a Source #
Check that the value's length is between N and M
notEmpty :: (Monad m, HasLength a) => e -> ValidationRuleT e m a Source #
Specialized minLength with N = 1
largerThan :: (Monad m, Ord a) => a -> e -> ValidationRuleT e m a Source #
Check that a value is larger than N
smallerThan :: (Monad m, Ord a) => a -> e -> ValidationRuleT e m a Source #
Check that a value is smaller than N
valueBetween :: (Monad m, Ord a) => a -> a -> e -> ValidationRuleT e m a Source #
Check that a value is between M and N
matchesRegex :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, Monad m) => Regex -> e -> ValidationRuleT e m a Source #
Checks that a value matches a regular expression
conformsPred :: Monad m => (a -> Bool) -> e -> ValidationRuleT e m a Source #
Check that a value conforms a predicate
conformsPredM :: Monad m => (a -> m Bool) -> e -> ValidationRuleT e m a Source #
Check that a value conforms a predicate
Transforming checks
requiredValue :: Monad m => e -> TransValidationRuleT e m (Maybe a) a Source #
Check that an optional value is actually set to 'Just a'
nonEmptyList :: Monad m => e -> TransValidationRuleT e m [a] (NonEmpty a) Source #
Check that a list is not empty
conformsPredTrans :: Monad m => (a -> Maybe b) -> e -> TransValidationRuleT e m a b Source #
Do some check returning Nothing
if the value is invalid and 'Just a' otherwise.
conformsPredTransM :: Monad m => (a -> m (Maybe b)) -> e -> TransValidationRuleT e m a b Source #
Do some check returning Nothing
if the value is invalid and 'Just a' otherwise.
Helper classes and types
class HasLength a where Source #
All types that have a length, eg. String
, '[a]', 'Vector a', etc.
Instances
HasLength ByteString Source # | |
Defined in Data.Validator getLength :: ByteString -> Int64 Source # | |
HasLength ByteString Source # | |
Defined in Data.Validator getLength :: ByteString -> Int64 Source # | |
HasLength Text Source # | |
HasLength Text Source # | |
HasLength [a] Source # | |
Defined in Data.Validator |
class ConvertibleStrings a b where #
convertString :: a -> b #
Instances
64-bit signed integer type
Instances
Regular expression helpers
re :: QuasiQuoter #
A QuasiQuoter for regular expressions that does a compile time check.
mkRegexQQ :: [PCREOption] -> QuasiQuoter #
Returns a QuasiQuoter like re
, but with given PCRE options.