valor-0.0.0.1: Simple general structured validation library

Copyright© 2018 Luka Hadžiegrić
LicenseMIT
MaintainerLuka Hadžiegrić <reygoch@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Valor

Contents

Description

This module provides a general way for validating data. It was inspired by forma and digestive-functors and some of their shortcomings. In short, approach taken by the Valor is to try and parse the error from the data instead of data from some fixed structured format like the JSON.

Main feature of Valor is that you are not forced to use specific input type like JSON, or to use specific output type like 'digestive-functors' View. You can use what ever you like as an input and use custom error type as the output (although it does have to follow a specific format).

To use Valor you first need to have some "input" data type that you want to validate and an "error" data type that will store validation errors of your data. Although the "shapes" of your input and error data types can differ, in the most common use case your input and error would be of the same shape.

Here is an example:

data Article = Article
  { id      :: Int
  , title   :: String
  , content :: String
  , tags    :: [String]
  , author  :: User
  } deriving ( Show )

data ArticleError = ArticleError
  { id      :: Maybe String           -- ^ here I've intended for 'id' to have only one error message
  , title   :: Maybe [String]         -- ^ for 'title' field there might be many error messages
  , content :: Maybe [String]
  , tags    :: Maybe [Maybe [String]] -- ^ here every 'tag' can have multiple error messages (or none)
  , author  :: Maybe UserError        -- ^ here we have a possible 'UserError' in case validation fails
  } deriving ( Show )

--

data User = User
  { username :: String
  } deriving ( Show )

data UserError = UserError
  { username :: Maybe [String]
  } deriving ( Show )

You might think that this will introduce a lot of duplicated code, and you are right! But there is a solution. If you do not need the flexibility of this first approach, you can use provided Validatable type family to ease the pain (or even write your own type family, Valor doesn't care).

So, here is how the above code would look if we were to use type families:

{# LANGUAGE FlexibleInstances    #}
{# LANGUAGE StandaloneDeriving   #}
{# LANGUAGE TypeSynonymInstances #}

--

data Article' a = Article
  { id      :: Validatable a String           Int
  , title   :: Validatable a [String]         String
  , content :: Validatable a [String]         String
  , tags    :: Validatable a [Maybe [String]] [String]
  , author  :: Validatable a (User' a)        (User' a)
  }

type Article = Article' Identity
deriving instance Show Article

type ArticleError = Article' Validate
deriving instance Show ArticleError

--

data User' a = User
  { username :: Validatable a [String] String
  }

type User = User' Identity
deriving instance Show User

type UserError = User' Validate
deriving instance Show UserError

As you can see, we have to enable a couple of language extensions to allow us type class derivation with this approach.

Validatable is basically a type level function that takes three arguments and returns a type.

  • First argument has kind * -> * which means it is a type that takes another type as an argument to make a concrete type. One common example of this is Maybe. In this case however, we can pass in Identity to Article' to create our "value/input" type and Validate to create our "error" type. If we pass in any other type it will just get applied to the third argument (which is basic field value of our input type).
  • Second argument is the type we want to use for storing error(s). This will be the resulting type of Validatable but wrapped in Maybe if we apply Validate.
  • Third argument is the basic value type for the field of our input type. This will be the resulting type in case we apply Identity

Synopsis

Constructing a Validator

data Validator i m e Source #

Now that we have defined our input and error data types we can start constructing a Validator for our data. In essence validator is just a function that takes in an input i and returns an error e wrapped in a monad m if your input was invalid.

Validator is an Applicative and you can construct a new one by using functions: skip, check, mapCheck, checks, mapChecks, subValidator and mapSubValidator. Those functions have to be provided with actual checks to perform, and we define a single check by using ExceptT, so let's create some simple checks to perform on our data:

over18 :: Monad m => Int -> ExceptT String m Int
over18 n
  | n < 18    = throwE "must be over 18"
  | otherwise = pure n

nonempty :: Monad m => String -> ExceptT [String] m String
nonempty s
  | length s == 0 = throwE ["can't be empty"]
  | otherwise     = pure s

nonbollocks :: Monad m => String -> ExceptT [String] m String
nonbollocks s
  | s == "bollocks" = throwE ["can't be bollocks"]
  | otherwise       = pure s

nonshort :: Monad m => String -> ExceptT [String] m String
nonshort s = if length s < 10 then throwE ["too short"] else pure s

With this we can finally create Validators for our User and Article data types:

articleValidator :: Monad m => Validator Article m ArticleError
articleValidator = Article
  <$> check        id      over18
  <*> checks       title   [nonempty, nonbollocks]
  <*> checks       content [nonempty, nonbollocks, nonshort]
  <*> mapChecks    tags    [nonempty, nonbollocks]
  <*> subValidator author  userValidator

userValidator :: Monad m => Validator User m UserError
userValidator = User
  <$> checks username [nonempty, nonbollocks]

Instances

Functor m => Functor (Validator i m) Source # 

Methods

fmap :: (a -> b) -> Validator i m a -> Validator i m b #

(<$) :: a -> Validator i m b -> Validator i m a #

Applicative m => Applicative (Validator i m) Source # 

Methods

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 # 

Methods

(<>) :: Validator i m e -> Validator i m e -> Validator i m e #

sconcat :: NonEmpty (Validator i m e) -> Validator i m e #

stimes :: Integral b => b -> Validator i m e -> Validator i m e #

skip Source #

Arguments

:: Applicative m 
=> Validator i m (Maybe e)

just a dummy validator that always succeeds.

skip is used when you are not interested in validating certain fields.

check Source #

Arguments

:: (Functor m, Monoid e) 
=> (i -> x)

field selector

-> (x -> ExceptT e m x)

check to be performed

-> Validator i m (Maybe e)

resulting validator

Check if a single condition is satisfied.

checks Source #

Arguments

:: (Applicative m, Monoid e, Semigroup e) 
=> (i -> x)

field selector

-> [x -> ExceptT e m x]

list of checks

-> Validator i m (Maybe e)

resulting validator

Check if mutiple conditions are satisfied.

mapCheck Source #

Arguments

:: (Traversable f, Monad m, Monoid e) 
=> (i -> f x)

field selector

-> (x -> ExceptT e m x)

check to be performed

-> Validator i m (Maybe (f (Maybe e)))

resulting validator

Apply a single check to multiple values within Traversable structure.

mapChecks Source #

Arguments

:: (Monad m, Monoid e, Traversable f, Semigroup (f (Maybe e))) 
=> (i -> f x)

field selector

-> [x -> ExceptT e m x]

list of checks

-> Validator i m (Maybe (f (Maybe e)))

resulting validator

Apply a multiple checks to values within Traversable structure.

subValidator Source #

Arguments

:: Functor m 
=> (i -> x)

field selector

-> Validator x m e

Validator to run against field value

-> Validator i m (Maybe e)

resulting Validator

Apply a Validator instead of check to the field. This is useful when validating nested records.

mapSubValidator Source #

Arguments

:: (Monad m, Traversable f) 
=> (i -> f x)

field selector

-> Validator x m e

Validator to run against values

-> Validator i m (Maybe (f (Maybe e)))

resulting Validator

Validating the data

validate Source #

Arguments

:: Functor m 
=> Validator i m e

Validator that we want to run against the value

-> i

value that is being validated

-> m (Maybe e)

final result wrapped in a monad of our choosing

Once you have constructed your Validator you can run it against your input data. If there were no validation errors you will get Nothing wrapped in a monad of your choice as a result.

Here is the result of running articleValidator against some bad data:

badArticle :: Article
badArticle = Article
  { id      = 17
  , title   = "Some interesting title"
  , content = "bollocks"
  , tags    = ["I'm ok", "me too", "bollocks"]
  , author  = badUser
  }

badUser :: User
badUser = User ""
>>> validatePure articleValidator badArticle
Just
  ( Article
    { id = Just "must be over 18"
    , title = Nothing
    , content = Just ["can't be bollocks","too short"]
    , tags = Just [Nothing,Nothing,Just ["can't be bollocks"]]
    , author = Just (User {username = Just ["can't be empty"]})
    }
  )

validatePure :: Validator i Identity e -> i -> Maybe e Source #

This will run your Validator as a pure computation returning simple Maybe instead of it being wrapped in some monad.

Utilities

data Validate a Source #

Tag used with type family to tell the compiler that we are constructing the "error" record.

type family Validatable a e x where ... Source #

A simple type family used for constructing your data structure.

Equations

Validatable Validate e x = Maybe e 
Validatable Identity e x = x 
Validatable a e x = a x 

Convenient re-exports

newtype Identity a :: * -> * #

Identity functor and monad. (a non-strict monad)

Since: 4.8.0.0

Constructors

Identity 

Fields

Instances

Monad Identity

Since: 4.8.0.0

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity

Since: 4.8.0.0

Methods

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

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

MonadFix Identity

Since: 4.8.0.0

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity

Since: 4.8.0.0

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity

Since: 4.8.0.0

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity 

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Eq1 Identity

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Ord1 Identity

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering #

Read1 Identity

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Identity a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Identity a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Identity a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a] #

Show1 Identity

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS #

Bounded a => Bounded (Identity a) 
Enum a => Enum (Identity a) 
Eq a => Eq (Identity a) 

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Floating a => Floating (Identity a) 
Fractional a => Fractional (Identity a) 
Integral a => Integral (Identity a) 
Num a => Num (Identity a) 
Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: 4.8.0.0

Real a => Real (Identity a) 

Methods

toRational :: Identity a -> Rational #

RealFloat a => RealFloat (Identity a) 
RealFrac a => RealFrac (Identity a) 

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: 4.8.0.0

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Ix a => Ix (Identity a) 
Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Semigroup a => Semigroup (Identity a)

Since: 4.9.0.0

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Storable a => Storable (Identity a) 

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Bits a => Bits (Identity a) 
FiniteBits a => FiniteBits (Identity a) 
Generic1 * Identity 

Associated Types

type Rep1 Identity (f :: Identity -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Identity f a #

to1 :: Rep1 Identity f a -> f a #

type Rep (Identity a) 
type Rep (Identity a) = D1 * (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 * (MetaCons "Identity" PrefixI True) (S1 * (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))
type Rep1 * Identity 
type Rep1 * Identity = D1 * (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 * (MetaCons "Identity" PrefixI True) (S1 * (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

data ExceptT e (m :: * -> *) a :: * -> (* -> *) -> * -> * #

A monad transformer that adds exceptions to other monads.

ExceptT constructs a monad parameterized over two things:

  • e - The exception type.
  • m - The inner monad.

The return function yields a computation that produces the given value, while >>= sequences two subcomputations, exiting on the first exception.

Instances

MonadTrans (ExceptT e) 

Methods

lift :: Monad m => m a -> ExceptT e m a #

Monad m => Monad (ExceptT e m) 

Methods

(>>=) :: ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b #

(>>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

return :: a -> ExceptT e m a #

fail :: String -> ExceptT e m a #

Functor m => Functor (ExceptT e m) 

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b #

(<$) :: a -> ExceptT e m b -> ExceptT e m a #

MonadFix m => MonadFix (ExceptT e m) 

Methods

mfix :: (a -> ExceptT e m a) -> ExceptT e m a #

MonadFail m => MonadFail (ExceptT e m) 

Methods

fail :: String -> ExceptT e m a #

(Functor m, Monad m) => Applicative (ExceptT e m) 

Methods

pure :: a -> ExceptT e m a #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b #

liftA2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a #

Foldable f => Foldable (ExceptT e f) 

Methods

fold :: Monoid m => ExceptT e f m -> m #

foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldr1 :: (a -> a -> a) -> ExceptT e f a -> a #

foldl1 :: (a -> a -> a) -> ExceptT e f a -> a #

toList :: ExceptT e f a -> [a] #

null :: ExceptT e f a -> Bool #

length :: ExceptT e f a -> Int #

elem :: Eq a => a -> ExceptT e f a -> Bool #

maximum :: Ord a => ExceptT e f a -> a #

minimum :: Ord a => ExceptT e f a -> a #

sum :: Num a => ExceptT e f a -> a #

product :: Num a => ExceptT e f a -> a #

Traversable f => Traversable (ExceptT e f) 

Methods

traverse :: Applicative f => (a -> f b) -> ExceptT e f a -> f (ExceptT e f b) #

sequenceA :: Applicative f => ExceptT e f (f a) -> f (ExceptT e f a) #

mapM :: Monad m => (a -> m b) -> ExceptT e f a -> m (ExceptT e f b) #

sequence :: Monad m => ExceptT e f (m a) -> m (ExceptT e f a) #

(Eq e, Eq1 m) => Eq1 (ExceptT e m) 

Methods

liftEq :: (a -> b -> Bool) -> ExceptT e m a -> ExceptT e m b -> Bool #

(Ord e, Ord1 m) => Ord1 (ExceptT e m) 

Methods

liftCompare :: (a -> b -> Ordering) -> ExceptT e m a -> ExceptT e m b -> Ordering #

(Read e, Read1 m) => Read1 (ExceptT e m) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ExceptT e m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ExceptT e m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ExceptT e m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ExceptT e m a] #

(Show e, Show1 m) => Show1 (ExceptT e m) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ExceptT e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ExceptT e m a] -> ShowS #

MonadZip m => MonadZip (ExceptT e m) 

Methods

mzip :: ExceptT e m a -> ExceptT e m b -> ExceptT e m (a, b) #

mzipWith :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

munzip :: ExceptT e m (a, b) -> (ExceptT e m a, ExceptT e m b) #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 

Methods

empty :: ExceptT e m a #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

some :: ExceptT e m a -> ExceptT e m [a] #

many :: ExceptT e m a -> ExceptT e m [a] #

(Monad m, Monoid e) => MonadPlus (ExceptT e m) 

Methods

mzero :: ExceptT e m a #

mplus :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) 

Methods

(==) :: ExceptT e m a -> ExceptT e m a -> Bool #

(/=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) 

Methods

compare :: ExceptT e m a -> ExceptT e m a -> Ordering #

(<) :: ExceptT e m a -> ExceptT e m a -> Bool #

(<=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>=) :: ExceptT e m a -> ExceptT e m a -> Bool #

max :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

min :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

(Read e, Read1 m, Read a) => Read (ExceptT e m a) 

Methods

readsPrec :: Int -> ReadS (ExceptT e m a) #

readList :: ReadS [ExceptT e m a] #

readPrec :: ReadPrec (ExceptT e m a) #

readListPrec :: ReadPrec [ExceptT e m a] #

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS #

show :: ExceptT e m a -> String #

showList :: [ExceptT e m a] -> ShowS #

runExceptT :: ExceptT e m a -> m (Either e a) #

The inverse of ExceptT.

throwE :: Monad m => e -> ExceptT e m a #

Signal an exception value e.