Copyright | © 2018 Luka Hadžiegrić |
---|---|
License | MIT |
Maintainer | Luka Hadžiegrić <reygoch@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Validate e
- type family Validatable a e x where ...
- data Validator i m e
- skip :: Applicative m => Validator i m (Maybe e)
- check :: forall i x m e. Monad m => (i -> x) -> (x -> ExceptT e m x) -> Validator i m (Maybe e)
- mapCheck :: forall i f x m e. (Monad m, Traversable f) => (i -> f x) -> (x -> ExceptT e m x) -> Validator i m (Maybe (f (Maybe e)))
- checks :: forall i x m e. (Monad m, Semigroup e) => (i -> x) -> [x -> ExceptT e m x] -> Validator i m (Maybe e)
- mapChecks :: forall i f x m e. (Monad m, Traversable f, Monoid e) => (i -> f x) -> [x -> ExceptT e m x] -> Validator i m (Maybe (f (Maybe e)))
- subValidator :: forall i x m e. Functor m => (i -> x) -> Validator x m e -> Validator i m (Maybe e)
- mapSubValidator :: forall i f x m e. (Monad m, Traversable f) => (i -> f x) -> Validator x m e -> Validator i m (Maybe (f (Maybe e)))
- validate :: Functor m => Validator i m e -> i -> m (Maybe e)
- validatePure :: Validator i Identity e -> i -> Maybe e
Introduction
Valor strives to be a simple and easy to use data validation library, that returns errors in a structured format. It is mainly focused on validating records, but with enough imagination you can validate anything (I think).
The usual approach to validating that most validation libraries (like digestive-functors and forma) take is to act as a parser that tries to parse the input data into some output data and returns an error if it doesn't succeed.
Valors approach is to leave the parsing to parsing libraries and instead try
to "parse" the error from already parsed data instead of the data it
self. This approach is more transparent since it doesn't force you to use any
intermediate types like JSON
which expects you to know, or learn how to
work with them, instead you decide what goes in and what comes out and have
(almost) full control over your data types.
Defining data types
A simple "tag" used to tell the Validatable
type family that we are
constructing the "error" type.
type family Validatable a e x where ... Source #
A simple type level function that is usefull to get rid of the boilerplate in case you want your error and data type to have the same shape / structure.
It takes in three arguments:
a
- A type with a kind of
* -> *
that basically serves as a flag which determines ifValidatable
will return the error type wrapped inMaybe
or a value type. To return the error type useValidate
and to return value type useIdentity
. e
- Type that should be used for the error.
x
- Type that should be used for the value.
Here is an example of how to use it to reduce boilerplate, instead of this (sill perfectly acceptable by Valor):
{ -# LANGUAGE DuplicateRecordFields #- } -- module Test -- import Data.Text (Text
) -- data User = User { username ::Text
, password ::Text
} deriving (Show
) data UserError = UserError { username ::Maybe
String
-- this field will have only one error , password ::Maybe
[String
] -- this one can have multiple errors } deriving (Show
)
which can get painful to maintain an repetitive to write if you have a lot of fields in your records, you can just write the following:
{ -# LANGUAGE FlexibleInstances #- } { -# LANGUAGE StandaloneDeriving #- } { -# LANGUAGE TypeSynonymInstances #- } -- module Test -- import Data.Valor (Validatable
,Validate
) import Data.Text (Text
) import Data.Functor.Identity (Identity
(..) ) -- data User' a = User { username ::Validatable
aString
Text
, password ::Validatable
a [String
]Text
} type User = User'Identity
deriving instanceShow
User type UserError = User'Validate
deriving instanceShow
UserError
This approach requires a few language extensions to allow us instance derivation, but it removes a lot of the boilerplate and maintenance costs in the long run.
All in all, Validatable
is quite easy to understand, it takes around 5 min
to understand this type family even if you've never used type families before
, just take a look at the Equations below:
Validatable Validate e x = Maybe e | |
Validatable Identity e x = x | |
Validatable a e x = a x |
Creating a Validator
Validator
is basically a function that takes in an input i
and returns
an error e
wrapped in your monad of choice m
.
To construct a Validator
you can use functions skip
, check
, mapCheck
,
checks
, mapChecks
, subValidator
and mapSubValidator
. Intended way of
constructing a Validator
is by using the Applicative
interface.
Above mentioned functions expect a test (or tests) in the form of
x -> ExceptT e m x
. ExceptT
was chosen here because it is a monad
transformer and allows ust to throw an error and use a custom monad m
.
This is useful in case you have to check the database to validate some data
or your test relies on success or failure of another field. You can use state
monad or transformer to pass in the data being validated so that it is
accessible within the test.
To run your Validator
against some data you can use validate
function, or
validatePure
if you don't want to use any particular monad and get the pure
result wrapped in Maybe
.
Here is an example of a few simple tests and construction of a Validator
for the previously defined User
record:
nonempty' ::Monad
m =>Text
->ExceptT
String
mText
nonempty' t = ifnull
t thenthrowE
"can't be empty" elsepure
t nonempty ::Monad
m =>Text
->ExceptT
[String
] mText
nonempty t = ifnull
t thenthrowE
["can't be empty"] elsepure
t nonbollocks ::Monad
m =>Text
->ExceptT
[String
] mText
nonbollocks t = if t == "bollocks" thenthrowE
["can't be bollocks"] elsepure
t nonshort ::Monad
m =>Text
->ExceptT
[String
] mText
nonshort t = iflength
t < 10 thenthrowE
["too short"] elsepure
t
userValidator ::Monad
m =>Validator
User m UserError userValidator = User<$>
check
email nonempty'<*>
checks
username [nonempty, nonbollocks, nonshort]
Instances
Functor m => Functor (Validator i m) Source # | |
Applicative m => Applicative (Validator i m) Source # | |
Defined in Data.Valor pure :: a -> Validator i m a # (<*>) :: Validator i m (a -> b) -> Validator i m a -> Validator i m b # liftA2 :: (a -> b -> c) -> Validator i m a -> Validator i m b -> Validator i m c # (*>) :: Validator i m a -> Validator i m b -> Validator i m b # (<*) :: Validator i m a -> Validator i m b -> Validator i m a # | |
(Applicative m, Semigroup e) => Semigroup (Validator i m e) Source # | |
(Applicative m, Semigroup e) => Monoid (Validator i m e) Source # | |
:: Applicative m | |
=> Validator i m (Maybe e) |
|
Use this in case you are not interested in validating a certain field.
:: Monad m | |
=> (i -> x) | field selector |
-> (x -> ExceptT e m x) | field check |
-> Validator i m (Maybe e) | resulting |
Runs a single check against the specified field.
:: (Monad m, Traversable f) | |
=> (i -> f x) | field selector |
-> (x -> ExceptT e m x) | field check |
-> Validator i m (Maybe (f (Maybe e))) | resulting |
Runs a single check over every element of some Traversable
"container".
This is quite useful if you for example have a field that contains array of items and you want to run a check against every single element of that list instead of the list as a whole.
:: (Monad m, Semigroup e) | |
=> (i -> x) | field selector |
-> [x -> ExceptT e m x] | list of field checks |
-> Validator i m (Maybe e) | resulting |
Runs multiple checks against the specified field. Resulting error must be a
Semigroup
so that it can be combined or accumulated in some fashion,
most convenient thing would be to use a list of "something".
:: (Monad m, Traversable f, Monoid e) | |
=> (i -> f x) | field selector |
-> [x -> ExceptT e m x] | list of field checks |
-> Validator i m (Maybe (f (Maybe e))) | resulting |
Basically the same thing as mapCheck
but it allows you to run multiple
checks per element.
:: Functor m | |
=> (i -> x) | field selector |
-> Validator x m e | custom field |
-> Validator i m (Maybe e) | resulting |
Runs a custom made Validator
against the field data.
:: (Monad m, Traversable f) | |
=> (i -> f x) | field selector |
-> Validator x m e | custom field |
-> Validator i m (Maybe (f (Maybe e))) | resulting |
Runs a custom made Validator
against the every element in a
Traversable
container.
Validating data
:: Validator i Identity e |
|
-> i | input data that you want to validate |
-> Maybe e | result of the validation |
In case you don't have a need for a monad you can use this function to run
your Validator
and get pure Maybe
instead of Maybe
wrapped in a monad.
Here is an example of running userValidator
over some invalid data:
badUser :: User badUser = User "boaty@mcboatface.com" "bollocks"
>>>validatePure
userValidator badUserJust
(User {email =Nothing
, username =Just
["can't be bollocks","too short"]})