validate-input-0.3.0.0: Input validation combinator library

Safe HaskellNone
LanguageHaskell2010

Data.Validator

Contents

Synopsis

Core monad and runners

type ValidationM e = ValidationT e Identity Source

The validation monad

data ValidationT e m a Source

The validation monad transformer

type ValidationRule e a = ValidationRuleT e Identity a Source

A validation rule. Combine using (>=>) or (<=<)

type ValidationRuleT e m a = a -> ValidationT e m a Source

A validation rule. Combine using (>=>) or (<=<)

runValidator :: ValidationRule e a -> a -> Either e a Source

Run a validation on a type a

runValidatorT :: Monad m => ValidationRuleT e m a -> a -> m (Either e a) 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 Kleisli composition of monads.

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped

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

Helper classes and types

class HasLength a where Source

All types that have a length, eg. String, '[a]', 'Vector a', etc.

Methods

getLength :: a -> Int64 Source

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.

data Regex :: *

An abstract pointer to a compiled PCRE Regex structure The structure allocated by the PCRE library will be deallocated automatically by the Haskell storage manager.

Instances