menshen-0.0.3: Data Validation

Copyright(c) 2019 Daniel YU
LicenseBSD3
MaintainerDaniel YU <leptonyu@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Menshen

Contents

Description

Data Validation inspired by JSR305

Synopsis

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.

Minimal complete definition

Nothing

Methods

invalid :: HasI18n a => a -> m b Source #

mark :: String -> m a -> m a Source #

Instances
HasValid VerifyResult Source # 
Instance details

Defined in Data.Menshen

HasValid (Either String) Source # 
Instance details

Defined in Data.Menshen

type Validator a = forall m. HasValid m => m a -> m a Source #

Validator, use to define detailed validation check.

class Exception e => HasI18n e where Source #

Plan for i18n translate, now just for english.

Minimal complete definition

toI18n

Methods

toI18n :: e -> String Source #

toErr :: String -> e -> ValidatorErr Source #

data ValidatorErr Source #

Instances
Show ValidatorErr Source # 
Instance details

Defined in Data.Menshen

data VerifyResult a Source #

Constructors

Invalid [ValidatorErr] 
Valid a 
Instances
Monad VerifyResult Source # 
Instance details

Defined in Data.Menshen

Functor VerifyResult Source # 
Instance details

Defined in Data.Menshen

Methods

fmap :: (a -> b) -> VerifyResult a -> VerifyResult b #

(<$) :: a -> VerifyResult b -> VerifyResult a #

Applicative VerifyResult Source # 
Instance details

Defined in Data.Menshen

HasValid VerifyResult Source # 
Instance details

Defined in Data.Menshen

Show a => Show (VerifyResult a) Source # 
Instance details

Defined in Data.Menshen

Validation Functions

class HasValidSize a where Source #

Length checker bundle

Minimal complete definition

getLength

Methods

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

notNull :: Validator (Maybe a) Source #

Assert not null

assertNull :: Validator (Maybe a) Source #

Assert null

positive :: (Eq a, Num a) => Validator a Source #

Positive validation

positiveOrZero :: (Eq a, Num a) => Validator a Source #

Positive or zero validation

negative :: (Eq a, Num a) => Validator a Source #

Negative validation

negativeOrZero :: (Eq a, Num a) => Validator a Source #

Negative or zero validation

minInt :: Integral a => a -> Validator a Source #

Minimum int validation

maxInt :: Integral a => a -> Validator a Source #

Maximum int validation

minDecimal :: RealFloat a => a -> Validator a Source #

Minimum int validation

maxDecimal :: RealFloat a => a -> Validator a Source #

Maximum decimal validation

pattern :: RegexLike Regex a => String -> Validator a Source #

Regular expression validation

email :: RegexLike Regex a => Validator a Source #

Email 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.

vcvt :: Validator' a -> Validator a Source #

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.