Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines the ValidateT
monad transformer and MonadValidate
typeclass. As the
names imply, they are intended to be used to write data validators, but they are general enough
that you may find other uses for them, too. For an overview of this library’s functionality, see
the documentation for ValidateT
.
Synopsis
- data ValidateT e m a
- runValidateT :: forall e m a. Functor m => ValidateT e m a -> m (Either e a)
- execValidateT :: forall e m a. (Monoid e, Functor m) => ValidateT e m a -> m e
- embedValidateT :: forall e m a. MonadValidate e m => ValidateT e m a -> m a
- mapErrors :: forall e1 e2 m a. (Monad m, Semigroup e2) => (e1 -> e2) -> ValidateT e1 m a -> ValidateT e2 m a
- class (Monad m, Semigroup e) => MonadValidate e m | m -> e where
- exceptToValidate :: forall e m a. MonadValidate e m => ExceptT e m a -> m a
- exceptToValidateWith :: forall e1 e2 m a. MonadValidate e2 m => (e1 -> e2) -> ExceptT e1 m a -> m a
- validateToError :: forall e m a. MonadError e m => ValidateT e m a -> m a
- validateToErrorWith :: forall e1 e2 m a. MonadError e2 m => (e1 -> e2) -> ValidateT e1 m a -> m a
- type Validate e = ValidateT e Identity
- runValidate :: forall e a. Validate e a -> Either e a
- execValidate :: forall e a. Monoid e => Validate e a -> e
The ValidateT
monad transformer
ValidateT
is a monad transformer for writing validations. Like ExceptT
, ValidateT
is
primarily concerned with the production of errors, but it differs from ExceptT
in that ValidateT
is designed not to necessarily halt on the first error. Instead, it provides a mechanism for
collecting many warnings or errors, ideally as many as possible, before failing. In that sense,
ValidateT
is also somewhat like WriterT
, but it is not just a combination
of ExceptT
and WriterT
. Specifically, it differs in the following two
respects:
ValidateT
automatically collects errors from all branches of anApplicative
expression, making it possible to write code in the same style that one would use withExceptT
and automatically get additional information for free. (This is especially true when used in combination with theApplicativeDo
language extension.)ValidateT
provides error signaling operators,refute
anddispute
, which are similar tothrowError
andtell
, respectively. However, both operators combine raised errors into a single value (using an arbitrarySemigroup
), so the relative ordering of validation errors is properly respected. (Of course, if the order doesn’t matter to you, you can choose to accumulate errors into an unordered container.)
An introduction to ValidateT
The first of the above two points is by far the most interesting feature of ValidateT
. Let’s make
it more concrete with an example:
>>>runValidate
(refute
["bang"]*>
refute
["boom"])Left
["bang", "boom"]
At first blush, the above example may lead you to believe that refute
is like tell
from
WriterT
, but it is actually more like throwError
. Consider its type:
refute
::MonadValidate
e m => e -> m a
Note that, like throwError
, refute
is polymorphic in its return type, which is to say it never
returns. Indeed, if we introduce a dependency on a computation that fails using refute
via
>>=
, the downstream computation will not be run:
>>> let getString =refute
["bang"]*>
pure
"boom" useString a =refute
[a] inrunValidate
(getString>>=
useString)Left
["bang"]
This works because although the Monad
instance for ValidateT
fails as soon as the first refute
is executed (as it must due to the way the second argument of >>=
depends on the result of its
first argument), the Applicative
instance runs all branches of <*>
and combines the errors
produced by all of them. When ApplicativeDo
is enabled, this can lead to some “magical” looking
error reporting where validation automatically continues on each sub-piece of a piece of data until
it absolutely cannot proceed any further. As an example, this package’s test suite includes the
following function:
validateQueryRequest :: (MonadReader
Env m,MonadValidate
[Error] m) => Value -> m QueryRequest validateQueryRequest req = withObject "request" req$
o -> do qrAuth <- withKey o "auth_token" parseAuthToken ~(qrTable, info) <- withKey o "table" parseTableName qrQuery <- withKey o "query" parseQueryfor_
info$
tableInfo -> pushPath "query"$
validateQuery qrTable tableInfo (atIsAdmin qrAuth) qrQuerypure
QueryRequest { qrAuth, qrTable, qrQuery }
The above do
block parses and validates some JSON, and it’s written as straight line code, but
with ApplicativeDo
enabled (along with the -foptimal-applicative-do
option, which makes GHC try
a little harder), it still produces errors for all parts of the input document at once:
>>>flip
runReader
env.
runValidateT
$
validateQueryRequest [aesonQQ| { "auth_token": 123 , "table": { "name": "users" } , "query": { "add": [ { "lit": "42" } , { "select": "points" } ]} }|]Left
[ Error ["auth_token"] (JSONBadValue "string" (Number 123)) , Error ["table"] (JSONMissingKey "schema") , Error ["query", "add", "lit"] (JSONBadValue "number" (String "42")) ]
The penultimate statement in the do
block—the one with the call to validateQuery
—depends on
several of the bindings bound earlier in the same do
block, namely qrAuth
, info
, and
qrQuery
. Because of that, validateQuery
will not be executed so long as any of its dependencies
fail. As soon as they all succeed, their results will be passed to validateQuery
as usual, and
validation will continue.
The full details
Although ValidateT
(with ApplicativeDo
) may seem magical, of course, it is not. As alluded to
above, ValidateT
simply provides a <*>
implementation that collects errors produced by both
arguments rather than short-circuiting as soon as the first error is raised.
However, that explanation alone may raise some additional questions. What about the monad laws? When
ValidateT
is used in a monad transformer stack, what happens to side effects? And what are
ValidateT
’s performance characteristics? The remainder of this section discusses those topics.
ValidateT
and the Monad
laws
ValidateT
’s Applicative
and Monad
instances do not conform to a strict interpretation of the
Monad
laws, which dictate that <*>
must be equivalent to ap
. For ValidateT
, this is not true
if we consider “equivalent” to mean ==
. However, if we accept a slightly weaker notion of
equivalence, we can satisfy the laws. Specifically, we may use the definition that some Validate
action a
is equivalent to another action b
iff
- if
producesrunValidate
a
, thenRight
x
must producerunValidate
b
whereRight
yx
(and==
y==
is the usual Haskell==
), - and if
producesrunValidate
a
, thenLeft
x
must producerunValidate
b
(butLeft
yx
andy
may be unrelated).
In other words, our definition of equivalence is like ==
, except that we make no guarantees about
the contents of an error should one occur. However, we do guarantee that replacing <*>
with
ap
or vice versa will never change an error to a success or a success to an error, nor will it
change the value of a successful result in any way. To put it another way, ValidateT
provides
“best effort” error reporting: it will never return fewer errors than an equivalent use of
ExceptT
, but it might return more.
Using ValidateT
with other monad transformers
ValidateT
is a valid, lawful, generally well-behaved monad transformer, and it is safe to use
within a larger monad transformer stack. Instances for the most common mtl
-style typeclasses are
provided. However, be warned: many common monad transformers do not have sufficiently
order-independent Applicative
instances for ValidateT
’s Applicative
instance to actually
collect errors from multiple branches of a computation.
To understand why that might be, consider that StateT
must enforce a left-to-right evaluation
order for <*>
in order to thread the state through the computation. If the a
action in an
expression a
fails, then it is simply not possible to run <*>
bb
since b
may still depend
on the state that would have been produced by a
. Similarly, ExceptT
enforces a left-to-right
evaluation because it aborts a computation as soon as an error is thrown. Using ValidateT
with
these kinds of monad transformers will cause it to effectively degrade to
WriterT
over ExceptT
since it will not be able to gather any errors
produced by refute
beyond the first one.
However, even that isn’t the whole story, since the relative order of monads in a monad transformer
stack can affect things further. For example, while the StateT
monad transformer enforces
left-to-right evaluation order, it only does this for the monad underneath it, so although
will not be able to collect multiple errors, StateT
s (ValidateT
e)
will. Note, however, that those two types differ in other ways, too—running each to
completion results in different types:ValidateT
e
(State
s)
runState
(runValidateT
m) s :: (Either
e a, s)runValidate
(runStateT
m s) ::Either
e (a, s)
That kind of difference is generally true when using monad transformers—the two combinations of
ExceptT
and StateT
have the same types as above, for example—but because ValidateT
needs to be
on top of certain transformers for it to be useful, combining ValidateT
with certain transformers
may be of little practical use.
One way to identify which monad transformers are uncooperative in the aforementioned way is to look
at the constraints included in the context of the transformer’s Applicative
instance. Transformers
like StateT
have instances of the shape
instanceMonad
m =>Applicative
(StateT
s m)
which notably require Monad
instances just to implement Applicative
! However, this is not always
sufficient for distinguishing which functions or instances use <*>
and which use >>=
, especially
since many older libraries (which predate Applicative
) may include Monad
contraints even when
they only use features of Applicative
. The only way to be certain is to examine the
implementation (or conservatively write code that is explicitly restricted to Applicative
).
(As it happens, ValidateT
’s Applicative
is actually one such “uncooperative” instance itself: it
has a Monad
constraint in its context. It is possible to write an implementation of ValidateT
without that constraint, but its <*>
would necessarily leak space in the same way
WriterT
’s >>=
leaks space. If you have a reason to want the less efficient
but more permissive variant, please let the author of this library know, as she would probably find
it interesting.)
Performance characteristics of ValidateT
Although the interface to ValidateT
is minimal, there are surprisingly many different ways to
implement it, each with its own set of performance tradeoffs. Here is a quick summary of the choices
ValidateT
makes:
ValidateT
is strict in the set of errors it accumulates, which is to say it reduces them to weak head normal form (WHNF) viaseq
immediately upon any call torefute
ordispute
.- Furthermore, all of
ValidateT
’s operations, including<*>
, operate in constant space. This means, for example, that evaluating
will consume constant space regardless of the size ofsequence_
xsxs
, not counting any space consumed purely due to the relevantFoldable
instance’s traversal ofxs
. - Finally,
ValidateT
accumulates errors in a left-associative manner, which is to say that any uses ofrefute
ordispute
combine the existing set of errors,e
, with the added set of errors,e'
, via the expressione
.<>
e'
A good rule of thumb is that ValidateT
has similar performance characteristics to
, while types like foldl'
(<>
)Validation
from the either
package tend to
have similar performance characteristics to
. That decision has both significant
advantages and significant disadvantages; the following subsections elaborate further.foldr
(<>
)
<*>
takes constant space
Great care has been taken in the implementation of <*>
to ensure it does not leak space. Notably,
the same cannot be said for many existing implementations of similar concepts. For example, you
will find that executing the expression
let m () =pure
()*>
m () in m ()
may continuously allocate memory until it is exhausted for types such as Validation
(from the
either
package), but ValidateT
will execute it in constant space. This point may seem silly,
since the above definition of m ()
will never do anything useful, anyway, but the same point also
applies to operations like sequence_
.
In practice, this issue matters far less for types like Validation
than it does for ValidateT
,
as Validation
and its cousins don’t have a Monad
instance and do not generally experience the
same usage patterns. (The additional laziness they are capable of can sometimes even avoid the space
leak altogether.) However, it can be relevant more often for ValidateT
, so this implementation
makes choices to avoid the potential for the leak altogether.
Errors are accumulated using strict, left-associated <>
A major consequence of the decision to both strictly accumulate state and maintain constant space is
that ValidateT
’s internal applications of <>
to combine errors are naturally strict and
left-associated, not lazy and right-associated like they are for types like Validation
. If the
number of errors your validation generates is small, this difference is irrelevant, but if it is
large, the difference in association can prove disastrous if the Semigroup
you choose to
accumulate errors in is [a]
!
To make it painfully explicit why using [a]
can come back to bite you, consider that each time
ValidateT
executes
, given some existing collection of errors refute
e'e
, it (strictly)
evalutes e
to obtain a new collection of errors. Now consider the implications of that
if <>
e'e
is a ten thousand element list: <>
will have to traverse all ten thousand elements and
reallocate a fresh cons cell for every single one in order to build the new list, even if just one
element is being appended to the end! Unfortunately, the ubiquitous, built-in [a]
type is clearly
an exceptionally poor choice for this pattern of accumulation.
Fortunately, the solution is quite simple: use a different data structure. If order doesn’t matter,
use a Set
or HashSet
. If it does, but either LIFO consumption of the data is okay or you are
okay with paying to reverse the data once after collecting the errors, use
to accumulate elements in an efficient manner. If neither is true, use a data structure like
Dual
[a]Seq
that provides an efficient implementation of a functional queue. You can always convert back
to a plain list at the end once you’re done, if you have to.
Instances
execValidateT :: forall e m a. (Monoid e, Functor m) => ValidateT e m a -> m e Source #
Runs a ValidateT
computation, returning the errors on failure or mempty
on success. The
computation’s result, if any, is discarded.
>>>execValidate
(refute
["bang"]) ["bang"] >>>execValidate
@[] (pure
42) []
embedValidateT :: forall e m a. MonadValidate e m => ValidateT e m a -> m a Source #
Runs a ValidateT
transformer by interpreting it in an underlying transformer with a
MonadValidate
instance. That might seem like a strange thing to do, but it can be useful in
combination with mapErrors
to locally alter the error type in a larger ValidateT
computation.
For example:
throwsIntegers ::MonadValidate
[Integer
] m => m () throwsIntegers =dispute
[42] throwsBools ::MonadValidate
[Bool
] m => m () throwsBools =dispute
[False
] throwsBoth ::MonadValidate
[Either
Integer
Bool
] m => m () throwsBoth = doembedValidateT
$
mapErrors
(map
Left
) throwsIntegersembedValidateT
$
mapErrors
(map
Right
) throwsBools >>>runValidate
throwsBothLeft
[Left
42,Right
False]
Since: 1.1.0.0
mapErrors :: forall e1 e2 m a. (Monad m, Semigroup e2) => (e1 -> e2) -> ValidateT e1 m a -> ValidateT e2 m a Source #
The MonadValidate
class
class (Monad m, Semigroup e) => MonadValidate e m | m -> e where Source #
The class of validation monads, intended to be used to validate data structures while collecting
errors along the way. In a sense, MonadValidate
is like a combination of
MonadError
and MonadWriter
, but it isn’t
entirely like either. The two essential differences are:
- Unlike
throwError
, raising an error usingrefute
does not always abort the entire computation—it may only abort a local part of it. - Unlike
tell
, raising an error usingdispute
still causes the computation to globally fail, it just doesn’t affect local execution.
Instances must obey the following law:
dispute
≡void
.
tolerate
.
refute
For a more thorough explanation, with examples, see the documentation for
ValidateT
.
Raises a fatal validation error. Aborts the current branch of the validation (i.e. does not return).
>>>runValidate
(refute
["boom"]>>
refute
["bang"])Left
["boom"]
Raises a non-fatal validation error. The overall validation fails, and the error is recorded, but validation continues in an attempt to try and discover more errors.
>>>runValidate
(dispute
["boom"]>>
dispute
["bang"])Left
["boom", "bang"]
If not explicitly implemented, the default implementation is
(which must behave equivalently by law), but it is sometimes possible to provide a
more efficient implementation.void
.
tolerate
.
refute
tolerate :: m a -> m (Maybe a) Source #
behaves like tolerate
mm
, except that any fatal errors raised by refute
are altered
to non-fatal errors that return Nothing
. This allows m
’s result to be used for further
validation if it succeeds without preventing further validation from occurring upon failure.
>>>runValidate
(tolerate
(refute
["boom"])>>
refute
["bang"])Left
["boom", "bang"]
Since: 1.1.0.0
Instances
Converting between monads
exceptToValidate :: forall e m a. MonadValidate e m => ExceptT e m a -> m a Source #
Runs an ExceptT
computation, and if it raised an error, re-raises it using refute
. This
effectively converts a computation that uses ExceptT
(or MonadError
) into
one that uses MonadValidate
.
>>>runValidate
$
exceptToValidate
(pure
42)Right
42 >>>runValidate
$
exceptToValidate
(throwError
["boom"])Left
"boom"
Since: 1.2.0.0
exceptToValidateWith :: forall e1 e2 m a. MonadValidate e2 m => (e1 -> e2) -> ExceptT e1 m a -> m a Source #
Like exceptToValidate
, but additionally accepts a function, which is applied to the error
raised by ExceptT
before passing it to refute
. This can be useful if the original error type is
not a Semigroup
.
>>>runValidate
$
exceptToValidateWith
(:[]) (pure
42)Right
42 >>>runValidate
$
exceptToValidateWith
(:[]) (throwError
"boom")Left
["boom"]
Since: 1.2.0.0
validateToError :: forall e m a. MonadError e m => ValidateT e m a -> m a Source #
Runs a ValidateT
computation, and if it raised any errors, re-raises them using throwError
.
This effectively converts a computation that uses ValidateT
(or MonadValidate
) into one that
uses MonadError
.
>>>runExcept
$
validateToError
(pure
42)Right
42 >>>runExcept
$
validateToError
(refute
["boom"] *>refute
["bang"])Left
["boom", "bang"]
Since: 1.2.0.0
validateToErrorWith :: forall e1 e2 m a. MonadError e2 m => (e1 -> e2) -> ValidateT e1 m a -> m a Source #
Like validateToError
, but additionally accepts a function, which is applied to the errors
raised by ValidateT
before passing them to throwError
. This can be useful to concatenate
multiple errors into one.
>>>runExcept
$
validateToErrorWith
mconcat
(pure
42)Right
42 >>>runExcept
$
validateToErrorWith
mconcat
(refute
["boom"] *>refute
["bang"])Left
"boombang"
Since: 1.2.0.0
The Validate
monad
runValidate :: forall e a. Validate e a -> Either e a Source #
See runValidateT
.
execValidate :: forall e a. Monoid e => Validate e a -> e Source #
See execValidateT
.