Copyright | (c) 2019 Daniel YU |
---|---|
License | BSD3 |
Maintainer | Daniel YU <leptonyu@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Data Validation inspired by JSR305
Synopsis
- class Monad m => HasValid m where
- type Validator a = forall m. HasValid m => m a -> m a
- data ValidationException
- = ShouldBeFalse
- | ShouldBeTrue
- | ShouldNull
- | ShouldNotNull
- | InvalidSize Word64 Word64
- | InvalidPositive
- | InvalidPositiveOrZero
- | InvalidNegative
- | InvalidNegativeOrZero
- | InvalidMax Integer
- | InvalidMin Integer
- | InvalidEmail
- | InvalidNotBlank
- | InvalidNotEmpty
- | InvalidPast
- | InvalidFuture
- | InvalidPastOrPresent
- | InvalidFutureOrPresent
- | InvalidDecimalMax Scientific
- | InvalidDecimalMin Scientific
- | InvalidDigits Word8 Word8
- | InvalidPattern String
- class Exception e => HasI18n e where
- toI18n :: e -> String
- toErr :: String -> e -> ValidatorErr
- data ValidatorErr = ValidatorErr {}
- data VerifyResult a
- = Invalid [ValidatorErr]
- | Valid a
- class HasValidSize a where
- notNull :: Validator (Maybe a)
- assertNull :: Validator (Maybe a)
- assertTrue :: Validator Bool
- assertFalse :: Validator Bool
- positive :: (Eq a, Num a) => Validator a
- positiveOrZero :: (Eq a, Num a) => Validator a
- negative :: (Eq a, Num a) => Validator a
- negativeOrZero :: (Eq a, Num a) => Validator a
- minInt :: Integral a => a -> Validator a
- maxInt :: Integral a => a -> Validator a
- minDecimal :: RealFloat a => a -> Validator a
- maxDecimal :: RealFloat a => a -> Validator a
- pattern :: RegexLike Regex a => String -> Validator a
- email :: RegexLike Regex a => Validator a
- (?) :: HasValid m => m a -> Validator a -> m a
- verify :: HasValid m => a -> Validator a -> m a
- (?:) :: HasValid m => a -> Validator a -> m a
- vcvt :: Validator' a -> Validator a
- (=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target
How to use this library
This library is designed for validate haskell records, such as in configurations or web request parameters.
Usage:
{-# LANGUAGE RecordWildCards #-} module Main where import Data.Menshen data Body = Body { name :: String , age :: Int } deriving Show verifyBody :: Validator Body verifyBody = vcvt $ \Body{..} -> Body <$> name ?: mark "name" . pattern "^[a-z]{3,6}$" <*> age ?: mark "age" . minInt 1 . maxInt 150 makeBody :: String -> Int -> Either String Body makeBody name age = Body{..} ?: verifyBody main = do print $ makeBody "daniel" 15
Useage in Record parsing process:
instance HasValid Parser where invalid = fail . toI18n instance FromJSON Body where parseJSON = withObject "Body" $ \v -> Body <$> v .: "name" ? pattern "^[a-z]{3,6}$" <*> v .: "age" ? minInt 1 . maxInt 150
Definition
class Monad m => HasValid m where Source #
Define how invalid infomation passed to upper layer.
Nothing
Instances
HasValid VerifyResult Source # | |
Defined in Data.Menshen invalid :: HasI18n a => a -> VerifyResult b Source # mark :: String -> VerifyResult a -> VerifyResult a Source # | |
HasValid (Either String) Source # | |
type Validator a = forall m. HasValid m => m a -> m a Source #
Validator, use to define detailed validation check.
data ValidationException Source #
Validation Error Message
Instances
Show ValidationException Source # | |
Defined in Data.Menshen showsPrec :: Int -> ValidationException -> ShowS # show :: ValidationException -> String # showList :: [ValidationException] -> ShowS # | |
Exception ValidationException Source # | |
Defined in Data.Menshen | |
HasI18n ValidationException Source # | |
Defined in Data.Menshen toI18n :: ValidationException -> String Source # toErr :: String -> ValidationException -> ValidatorErr Source # |
class Exception e => HasI18n e where Source #
Plan for i18n translate, now just for english.
Instances
HasI18n ValidationException Source # | |
Defined in Data.Menshen toI18n :: ValidationException -> String Source # toErr :: String -> ValidationException -> ValidatorErr Source # |
data ValidatorErr Source #
Instances
Show ValidatorErr Source # | |
Defined in Data.Menshen showsPrec :: Int -> ValidatorErr -> ShowS # show :: ValidatorErr -> String # showList :: [ValidatorErr] -> ShowS # |
data VerifyResult a Source #
Invalid [ValidatorErr] | |
Valid a |
Instances
Validation Functions
class HasValidSize a where Source #
Length checker bundle
size :: (Word64, Word64) -> Validator a Source #
Size validation
notEmpty :: Validator a Source #
Assert not empty
notBlank :: Validator a Source #
Assert not blank
getLength :: a -> Word64 Source #
calculate length from value
Instances
HasValidSize Text Source # | |
HasValidSize Text Source # | |
HasValidSize [a] Source # | |
assertNull :: Validator (Maybe a) Source #
Assert null
assertTrue :: Validator Bool Source #
Assert true
assertFalse :: Validator Bool Source #
Assert false
minDecimal :: RealFloat a => a -> Validator a Source #
Minimum int validation
maxDecimal :: RealFloat a => a -> Validator a Source #
Maximum decimal validation
Validation Operations
(?) :: HasValid m => m a -> Validator a -> m a infixl 5 Source #
apply record validation to the value
verify :: HasValid m => a -> Validator a -> m a Source #
lift value a to validation context and check if it is valid.
(?:) :: HasValid m => a -> Validator a -> m a infixl 5 Source #
lift value a to validation context and check if it is valid.
Reexport Functions
(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target #
This is the pure functional matching operator. If the target
cannot be produced then some empty result will be returned. If
there is an error in processing, then error
will be called.