contracheck-applicative
This package provides some simple yet useful types and functions to dynamically check properties of your data.
Why use this library?
Runtime-checking for properties of data is the poor man's parsing. Nonetheless, sometimes it has do be done, and most of the time is not really pretty.
Most validation libraries define validations to be a type like a -> Either Text a
, which makes sense as it captures the essence of validations: Put something in, and you either get it back and know your data is alright, or you have an error to work with. But the type a -> Either Text a
does not behave nicely:
- On the type level it does not distinguish between unvalidated and validated values.
- Validations are not combinable: There is no canonical monoid instance
- Validations are not reusable: It is invariant; so it is neither co- nor contravariant.
- Validations are not composable: There is no canonical way to combine a pair of validations
(a -> Either Text a, b -> Either Text b)
to a validation (a, b) -> Either Text (a, b)
This library attempts to fix these issues.
Quickstart
A Check
is a function that takes an Unvalidated
value and returns the result, possibly with a context: If the input has Passed
the check or Failed
it with a number of possible errors.
newtype Unvalidated a = Unvalidated { unsafeValidate :: a }
data CheckResult
= Passed
| Failed (Seq a)
newtype Check e m a = Check { runCheck :: Unvalidated a -> m (CheckResult e) }
type Check' e = Check e Identity
Unvalidated
The Unvalidated
newtype is to make a distinction between validated and unvalidated values on the type level. It is often convient to give an orphan instance for the typeclass of your choice via -XStandaloneDeriving
so unvalidated data cannot get into your system, e.g.
{-# language StandaloneDeriving, GeneralizedNewtypeDeriving, DerivingStrategies #-}
import Data.Aeson(FromJSON)
deriving newtype instance (FromJSON a) => FromJSON (Unvalidated a)
CheckResult
It has a monoid instance so it collects all possible errors, that is, it is not lazy in its failure component.
Basically all this library does is provide convenient instances for these types.
Check
To start off lets give some simple examples. We construct Check
s using the auxiliary combinators
failsWith :: e -> CheckResult e
failsNoMsg :: CheckResult e
checking' :: (a -> CheckResult e) -> Check' e a
test' :: Applicative m => (a -> Bool) -> (a -> e) -> Check e m a
import Data.Char(isAlpha)
checkEven :: Check' String Int
checkEven = test
((== 0) . (`mod` 2))
(mappend "Number not even: " . show)
type Age = Int
checkAge = test' (< 18) failsNoMsg
type Name = String
checkName = test $ \name ->
let invalidChars = filter (not . isAlpha) name
in if null invalidChars
then Passed
else failsWith invalidChars
There are some other combinators to construct checks in various flavours.
You can run the checks using validateBy'
if you want to use the validated result or just by runCheck
if you just want to know if your input passed the check (or which errors occured).
Composition
The Check
type is contravariant in the parameter to be checked (in fact, the whole library is merely a big wrapper around the instances for the type classes from the package contravariant). This tells us that we can "pull back" checks to other types:
checkOdd = contramap (+1) checkEven
So if we have a Check
for an a
and know how to convert a b
into an a
that preserves the property to be checked, we get a Check
for our b
for free. You can also pull back a pair of checks to a product/sum of types ((,)/Either
) using divide/choose
from the type classes Divisible/Decidable
(also defined in the package contravariant). We show how to use them by lifting a Check
for an a
to a Check
for a list of a
s:
checkListBy :: Check' e a -> Check' e [a]
checkListBy checkA =
choose split checkNil checkCons
where
splitSum [] = Left ()
splitSum (x:xs) = Right (x, xs)
checkNil = mempty
checkCons = divide id checkA (checkListBy checkA)
To check a list [a]
we have to distinguish two cases (split
); either it is empty (Left ()
), then we apply the trivial check checkNil
or it is a cons, then we apply the check to the head and check the rest of the list.
To summarize, we can use (with Types specialized to Check
):
contramap
(≡ >$<
): (b -> a) -> Check e m a -> Check e m b
divide :: (a -> (b, c)) -> Check e m b -> Check e m c -> Check e m a
choose :: (a -> Either b c) -> Check e m b -> Check e m c -> Check e m a
Combination
But now you want to combine your checks, e.g. to check a registration form. A first attempt might be to use the monoid instance of CheckResult
. Note that it collects all errors and does not short-circuit if a Check
fails (as you do not want to be that guy that sends the registration form back twenty times with different errors). But fortunately the Monoid
-instance of CheckResult
lifts to Checks
! That means we can use the Semigroup/Monoid
operations on Checks
, (mempty
being the trivial Check
that always succeeds).
data Registration = Registration
{ registrationAge :: Age
, registrationName :: Name
, registrationEmail :: String
}
checkRegistration
= contramap registrationAge checkAge
<> contramap registrationName checkName
<> contramap registrationEmail mempty -- of course unneccessary as it does nothing, but here for completeness
Additional Context
Sometimes you need to check properties, but the check itself has a sideeffect e.g. making a HTTP request or reading from a database. This is no problem, as
Check
s may have a context (remember that Check' e a ≡ Check e Identity a
, a Check
with a trivial context).
- we can easily convert our checks between context as
Check
s are an instance of MFunctor
from the package mmorph.
- we are all good as long as the context is an
Applicative
as then the monoid instance of CheckResult e
lifts to m CheckResult e
.
Let's give an example. Say you let users store URLs in a database, but for their convience you do not accept broken links.
import Network.HTTP.Client
import Network.HTTP.Types.Status(Status, statusCode)
import Network.HTTP.Client.TLS(newTlsManager)
import Control.Concurrent.Async(concurrently)
import Control.Validation.Check
import Control.Monad.Morph(MFunctor(..), generalize)
newtype Url = Url { getUrl ∷ String }
deriving (Show, Eq, IsString)
checkUrlNo4xx ∷ Check Status IO Url
checkUrlNo4xx = checking $ \url → do
m ← newTlsManager
req ← parseRequest . getUrl $ url
res ← httpLbs req m
let stat = (responseStatus res) ∷Status
code = statusCode stat
pure $ if code < 400 || code >= 500
then Passed
else failsWith stat
But now you allow your users to store several links, Facbook, LinkedIn, Twitter and whatnot. With foldWithCheck
/traverseWithCheck
you can lift checks to arbitary instances of Foldable
or Traversable
:
foldWithCheck :: (Foldable f, Applicative m) => Check e m a -> Check e m (f a)
traverseWithCheck :: (Traversable t, Applicative m) => Check e m a -> Check e m (t a)
type UrlList = [ Url ]
checkUrlList :: Check Status IO [Url]
checkUrlList = traverseWithCheck checkUrlNo4xx
Thats all there is. Since it is that easy to generalize, Check
s for foldables/traversable are ommited.
Well, its not really performant, as the Url
s are checked in sequence. We can fix that by giving IO
a "parallel" Applicative
instance that performs all chained (<*>)
in concurrently:
newtype ParIO a = ParIO { runParIO :: IO a } deriving Functor
instance Applicative ParIO where
pure = ParIO . pure
ParIO iof <*> ParIO iox = ParIO $ (\(f, x) -> f x) <$> concurrently iof iox
As we do not want to change the implementation of checkUrlNo4xx
as it is fine on its own, but we can use hoist
to lift the check to a context that is executed concurrently:
-- hoist :: Monad m => (forall a. m a -> n a) -> Check e m a -> Check e n a
-- ParIO :: forall a. IO a -> ParIO a
checkUrlListPar :: Check Status ParIO [Url]
checkUrlListPar = traverseWithCheck (hoist ParIO checkUrlNo4xx)
Warning:
checkUrlListParWrong = hoist ParIO checkUrlList
does NOT work as here you lift into the parallel context after all the checks have been performed.
Thats about it.
Checkable typeclass
There is also a typeclass in Control.Validation.Class, but it has to be used with care as it does not perform any Checks on primitive types and this is often not what you want. You should probably use it only on nested structures made up solely from custom data types.