package yocaml

  1. Overview
  2. Docs

Generic validation of structured data

YOCaml is a framework for building static site generators (a very small build-system, biased towards building web applications), and not a static site generator. It therefore needs to be as versatile as possible to allow plugins capable of adapting to its delivery model to be associated with it later. A key point is the arbitrary management of data associated with a dependency used to construct an artefact. For example, we would like to be able to associate metadata with articles or pages.

In this tutorial, we'll look at how YOCaml can generically handle data sources in various formats (for example Yaml, Json or Toml) and how to build validators capable of transforming these data into OCaml values, to make them more comfortable to use.

This document is written in literate programming (using MDX) and the examples are executed (and enrich the unit test base by means of expectation tests).

In this guide, we will first see how YOCaml attempts to be generic about the data format describing metadata (associated with sources or injected into templates), however, in this guide, we will only focus on the validation part.

Description of a generic data model

In the first version of YOCaml, we built validation functions based on visitors and which took first-class modules as arguments, as handlers, to describe the validation strategy for a format describing metadata. This approach works (and has been used in YOCaml blogs) but it was still very verbose, requiring each validation function to take a module as an argument (and making the composition of validation functions laborious).

The new approach describes an intermediate representation described by the type Yocaml.Data.t (and Yocaml.Data.t). The representation chosen is very similar to that chosen by Ezjsonm, which is used as the basis for many serialisation/deserialisation libraries (ie: ocaml-yaml). The idea is to offer this data transformation flow:

                      Template variables
                              ▲
        Yaml ◄─┐    ┌─────────┘        ┌─►Article.metadata
               │    │                  │
        Json ◄─┤    │  ┌──►validation  ├─►string list
               │    │  │            │  │
        Toml ◄─┼───► Yocaml.Data.t  └─►├─►user option
               │     ▲                 │
        Sexp ◄─┤     └─projection ◄────┼─►Index.t
               │                       │
        ...  ◄─┘                       └─►...

Adding support for a metadata format in YOCaml basically consists of providing a my_format -> Yocaml.Data.t function and providing injection into a template consists of providing a Yocaml.Data.t -> my_template_format function.

And a validation function is a simple function Yocaml.Data.t -> ('a,'errors) result. So who tries to convert a value of type Yocaml.Data.t into an arbitrary OCaml value.

Relying on a common format for parsing data and injecting data into templates offers several benefits, primarily centered around convenience, efficiency, and maintainability. It also facilitates flexibility in adapting to changing requirements, particularly regarding the desired format of the data.

Modules Organisation

  • Yocaml.Data Describes an mostly compatible Ezjsonm AST that acts as a generic AST for describing metadata that can be exchanged between source documents and templates. To summarise, source metadata is ultimately projected into a value of type Yocaml.Data.t and data injected into templates is projected from values of type Yocaml.Data.t.
  • Yocaml.Data.Validation Used to validate data described by type Yocaml.Data.t to build validation pipelines. The aim of this module is to produce combinators for building validation pipelines that support nesting and that can transform any value described by the AST in Data into arbitrary OCaml values.

The set of tools for describing data lives in the module Yocaml.Data, and the set of tools for validating schemas lives in the module Yocaml.Data.Validation. Let's take a few shortcuts to make the article easier to read:

module D = Yocaml.Data
module V = Yocaml.Data.Validation

D will be used to describe values to be validated. And V is used to access the validation functions.

In many cases, there is a symmetry between the functions described in Yocaml.Data and Yocaml.Data.Validation. For example, Yocaml.Data.option is used to describe a value of type option and Yocaml.Data.Validation.option is used to validate a value of type option.

Implementation of validation function

The purpose of a validation function is to convert a value of type Yocaml.Data.t to an arbitrary OCaml value by applying, potentially, the verification of certain preconditions. Yocaml.Data.t relay on some primitive types (that should be sufficient for dealing with arbitrary values): Yocaml.Data.null, Yocaml.Data.bool, Yocaml.Data.int, Yocaml.Data.float, Yocaml.Data.string, Yocaml.Data.list and Yocaml.Data.record.

Validating simple shapes

Validating a "shape" consists of checking that a value of type Yocaml.Data.t (which is opaque overall) corresponds to an expected structure. For example, let's try to validate the value float 32.56 as a float:

# V.float (D.float 32.56) ;;
- : float V.validated_value = Ok 32.56

As you can see, the function returns a validated value (a result) with the value Ok 32.56. We gave it a value of type Yocaml.Data.t and Yocaml.Data.Validation.float tries to convert it into a float.

Let's try to validate an incorrect entry. For example, let's try to treat a Boolean as if it were an Integer:

# V.int (D.bool true) ;;
- : int V.validated_value =
Error (V.Invalid_shape {V.expected = "int"; given = Yocaml.Data.Bool true})

As you can see, Yocaml.Data.Validation.bool refuses to consider a number described as an integer to be validated. The error may seem a bit verbose, but in principle it is only used by the core of Yocaml, for reporting purposes.

To sum up, simple types are validated using a function that corresponds to them in the Yocaml.Data.Validation module, which is easy, isn't it? We could generalise a shape validation function in this way: Data.t -> 'a Data.Validation.validated_value.

The special case of strings

The validator for character strings works like the others, but it is possible to pass it an optional argument strict, which is a boolean that allows other shapes (int, bool, float to be considered as strings). By default, the flag is set to true, so the validation does not handle other shapes. As with the other shapes, it's easy to validate that a data item is indeed a string:

# V.string (D.string "hello world") ;;
- : string V.validated_value = Ok "hello world"

And if you decide to set the strict flag to true, it doesn't change the behaviour of the function :

# V.string ~strict:true (D.string "hello world") ;;
- : string V.validated_value = Ok "hello world"

As we're trying to validate a string, changing the flag to false doesn't change the behaviour either :

# V.string ~strict:false (D.string "hello world") ;;
- : string V.validated_value = Ok "hello world"

The impact of this flag can be seen when we try to process shapes that are not strings but could easily behave like one. For example, let's try to validate a boolean as a string:

# V.string (D.bool true) ;;
- : string V.validated_value =
Error
 (V.Invalid_shape
   {V.expected = "strict-string"; given = Yocaml.Data.Bool true})

However, if you validate the boolean as a non-strict string, it will be converted to a string and validated correctly:

# V.string ~strict:false (D.bool true) ;;
- : string V.validated_value = Ok "true"

This behaviour may seem strange, I grant you, but it is explained by the fact that it is often a third-party library that will produce a parsed representation of data and that it is this parsed data that will be converted into data described by Yocaml.Data.t. However, we will see later in the guide that it is also possible to manage this type of case using composition of validators.

Dealing with list

The first "complex type" is lists. But in fact, it works in exactly the same way as the previous ones, except that it is parameterised by a validator. By default, list validation imposes the same restrictions as OCaml's parametric polymorphism: all elements must be of the same type, so the validation function Yocaml.Data.Validation.list_of is used. For example, to validate a list of strings :

# V.(list_of string) (D.(list [string "hello"; string "world"])) ;;
- : string list V.validated_value = Ok ["hello"; "world"]

Now let's try to validate an invalid list!

let valid_string_list = V.(list_of string)
let invalid_list =
  let open D in
  list [
    string "hello"
  ; int 42
  ; string "world"
  ; bool false
  ]

Now that we have a peculiar list, we can attempt to validate it:

# valid_string_list invalid_list ;;
- : string list V.validated_value =
Error
 (V.Invalid_list
   {V.errors =
     Yocaml__.Nel.(::)
      ((3,
        V.Invalid_shape
         {V.expected = "strict-string"; given = Yocaml.Data.Bool false}),
       [(1,
         V.Invalid_shape
          {V.expected = "strict-string"; given = Yocaml.Data.Int 42})]);
    given =
     [Yocaml.Data.String "hello"; Yocaml.Data.Int 42;
      Yocaml.Data.String "world"; Yocaml.Data.Bool false]})

Holy Moly, the error is quite frightening! As mentioned earlier in the guide, errors essentially serve YOCaml in building quality reporting when executing tasks. Therefore, errors are somewhat verbose to maintain as much structure as possible (but also remain relatively generic). Here, we can observe that the validate function provides us with two things:

  • given: which is the list we attempted to validate
  • errors: which is a non-empty list (Yocaml.Nel) of errors and their positions in the list. Collecting all invalid cells may seem peculiar. However, from our perspective, this allows, in case of an error, to provide feedback to the user about all the cells they need to modify.

Regardless, the purpose of the validation framework is to be generic enough so that, ideally, one shouldn't have to worry about errors except during the reporting phase!

Dealing with records

Now, let's focus on records which require a bit more work to validate. We will use a type user as the validation subject, here is its specification:

type user = {
  username: string
; age: int
; nouns: string list
; email: string option
}

We can see that the fields username and age are required, and we can assume that the fields nouns and email are optional. (If no noun is given, it can be represented by an empty list).

The validation of such a structure uses the Yocaml.Data.Validation.record function (which is a validation function, similar to the ones we have seen previously), as well as the Yocaml.Data.Validation.required, Yocaml.Data.Validation.optional, and potentially Yocaml.Data.Validation.optional_or functions, along with the operators described in Yocaml.Data.Validation.Syntax.

Let's write a validation function for our type user:

let user_validation =
  let open Yocaml.Data.Validation in
  record (fun fields ->
    let+ username = required fields "username" string
    and+ age = required fields "age" int
    and+ nouns = optional_or  ~default:[] fields "nouns" (list_of string)
    and+ email = optional fields "email" string
    in
      { username; age; nouns; email }
  )

We can typecheck the function in order to see if it seems good.

# user_validation;;
- : D.t -> user Yocaml.Data.Validation.validated_value = <fun>

Let's use our function to represent several scenarios. Let's start with the happy path, when all the data is valid:

# user_validation D.(record [
    "username", string "JohnDoe42"
  ; "age", int 42
  ; "nouns", list_of string ["he"; "him"; "his"; "himself"]
  ; "email", string "jdoe@name.com"
  ]) ;;
- : user Yocaml.Data.Validation.validated_value =
Ok
 {username = "JohnDoe42"; age = 42; nouns = ["he"; "him"; "his"; "himself"];
  email = Some "jdoe@name.com"}

Let's continue our exploration by setting aside the optional arguments for now:

# user_validation D.(record [
    "username", string "JohnDoe42"
  ; "age", int 42
  ]) ;;
- : user Yocaml.Data.Validation.validated_value =
Ok {username = "JohnDoe42"; age = 42; nouns = []; email = None}

Let's make several mistakes now to see if all errors are properly collected:

let a_very_malformed_user =
  user_validation D.(record [
      "usernme", string "JohnDoe42"
    ; "age", bool true
    ; "nouns", list_of int [1;2;3;4]
    ])

Here, there is a typo in usernme (missing a), age has the wrong type, and neither does the list of nouns... what a mess! The error might be a bit verbose!

# a_very_malformed_user ;;
- : user Yocaml.Data.Validation.validated_value =
Error
 (Yocaml.Data.Validation.Invalid_record
   {Yocaml.Data.Validation.errors =
     Yocaml__.Nel.(::)
      (Yocaml.Data.Validation.Missing_field
        {Yocaml.Data.Validation.field = "username"},
       [Yocaml.Data.Validation.Invalid_field
         {Yocaml.Data.Validation.given = Yocaml.Data.Bool true;
          field = "age";
          error =
           Yocaml.Data.Validation.Invalid_shape
            {Yocaml.Data.Validation.expected = "int";
             given = Yocaml.Data.Bool true}};
        Yocaml.Data.Validation.Invalid_field
         {Yocaml.Data.Validation.given =
           Yocaml.Data.List
            [Yocaml.Data.Int 1; Yocaml.Data.Int 2; Yocaml.Data.Int 3;
             Yocaml.Data.Int 4];
          field = "nouns";
          error =
           Yocaml.Data.Validation.Invalid_list
            {Yocaml.Data.Validation.errors =
              Yocaml__.Nel.(::)
               ((3,
                 Yocaml.Data.Validation.Invalid_shape
                  {Yocaml.Data.Validation.expected = "strict-string";
                   given = Yocaml.Data.Int 4}),
                [(2,
                  Yocaml.Data.Validation.Invalid_shape
                   {Yocaml.Data.Validation.expected = "strict-string";
                    given = Yocaml.Data.Int 3});
                 (1,
                  Yocaml.Data.Validation.Invalid_shape
                   {Yocaml.Data.Validation.expected = "strict-string";
                    given = Yocaml.Data.Int 2});
                 (0,
                  Yocaml.Data.Validation.Invalid_shape
                   {Yocaml.Data.Validation.expected = "strict-string";
                    given = Yocaml.Data.Int 1})]);
             given =
              [Yocaml.Data.Int 1; Yocaml.Data.Int 2; Yocaml.Data.Int 3;
               Yocaml.Data.Int 4]}}]);
    given =
     [("usernme", Yocaml.Data.String "JohnDoe42");
      ("age", Yocaml.Data.Bool true);
      ("nouns",
       Yocaml.Data.List
        [Yocaml.Data.Int 1; Yocaml.Data.Int 2; Yocaml.Data.Int 3;
         Yocaml.Data.Int 4])]})

We have seen how to use regular validation shapes, and moreover, we have seen that it is possible to use, in the validation of records, the previous validators, but the reverse is also true, for example:

# V.list_of user_validation ;;
- : D.t -> user list V.validated_value = <fun>

Build a validator for lists of users! Excellent! It is partly for this reason that errors are so complex; they must be nestable and handle increasingly complex cases to ensure the reusability of validators.

Additional Validators

There are other additional validators that fit with common OCaml types. For example, the ability to compose, at validator level (and not at field validator level) with values of type option using Yocaml.Data.Validation.option.

Dealing with options

If our value can be an option of int, it can be expressed by the following validator:

let option_int = V.(option int)

Which validates data that is either int or null. So validating null leads to the result Ok None:

# option_int D.null ;;
- : int option V.validated_value = Ok None

Validating int 10 leads to the result Ok (Some 15):

# option_int (D.int 15) ;;
- : int option V.validated_value = Ok (Some 15)

An trying to validate something invalid leads to an error:

# option_int (D.string "15") ;;
- : int option V.validated_value =
Error (V.Invalid_shape {V.expected = "int"; given = Yocaml.Data.String "15"})

Dealing with products

We can also work with product types, for example, we can validate a pair of string and int in this way:

# V.(pair string int) D.(pair string int ("foo", 12)) ;;
- : (string * int) V.validated_value = Ok ("foo", 12)

And as with the other validators, we can see that they are relatively well composed, For example, let's take a look at this rather complicated validator:

let complicated_validator =
  let open Yocaml.Data.Validation in
  pair
    (option (list_of (pair int bool)))
    (list_of (option (pair bool int)))

Let's test it with a set of data, which is also very complicated!

#  D.(
    (pair
      (option (list_of (pair int bool)))
      (list_of (option (pair bool int))))
      (Some [1, true; 2, false], [Some (false, 1);
       None; Some (true, 10)]))
    |> complicated_validator ;;
- : ((int * bool) list option * (bool * int) option list)
    Yocaml.Data.Validation.validated_value
= Ok (Some [(1, true); (2, false)], [Some (false, 1); None; Some (true, 10)])

And in the same way, let's try to validate a pair that is invalid!

# V.(pair string int) D.(pair bool string (false, "foo")) ;;
- : (string * int) V.validated_value =
Error
 (V.Invalid_record
   {V.errors =
     Yocaml__.Nel.(::)
      (V.Invalid_field
        {V.given = Yocaml.Data.Bool false; field = "fst";
         error =
          V.Invalid_shape
           {V.expected = "strict-string"; given = Yocaml.Data.Bool false}},
       [V.Invalid_field
         {V.given = Yocaml.Data.String "foo"; field = "snd";
          error =
           V.Invalid_shape
            {V.expected = "int"; given = Yocaml.Data.String "foo"}}]);
    given =
     [("fst", Yocaml.Data.Bool false); ("snd", Yocaml.Data.String "foo")]})

Which gives us some information about how the products are encoded under the bonnet! In fact, a product is encoded as a record which has strictly only two fields, fst and snd. It is therefore important to use the functions in the Yocaml.Data module to build data sets (and this is why the AST of Yocaml.Data is private).

There are also Yocaml.Data.Validation.triple and Yocaml.Data.Validation.quad (but they are defined in terms of even, using the fact that a, b, c can be described as a pair: a, [b, c]` etc.). If, for example, you wanted to describe a validator for the type 'a * 'b * 'c * 'd * 'e you could proceed as follows:

# let quint v1 v2 v3 v4 v5 my_value =
    let open Yocaml.Data.Validation in
    my_value
    |> pair v1 (pair v2 (pair v3 (pair v4 v5)))
    |> Result.map (fun (x1, (x2, (x3, (x4, x5)))) ->
         x1, x2, x3, x4, x5
       )
val quint :
  (D.t -> 'a Yocaml.Data.Validation.validated_value) ->
  (D.t -> 'b Yocaml.Data.Validation.validated_value) ->
  (D.t -> 'c Yocaml.Data.Validation.validated_value) ->
  (D.t -> 'd Yocaml.Data.Validation.validated_value) ->
  (D.t -> 'e Yocaml.Data.Validation.validated_value) ->
  D.t -> ('a * 'b * 'c * 'd * 'e, V.value_error) result = <fun>

This is also how the tripl and quad functions mentioned above are implemented. Now that we can process products (including records), we can move on to describing sums!

Dealing with sums

Now that we can describe products, let's move on to describing sums. Firstly, there's a dedicated function for validating values of type either, which, like the type ('a * 'b) which is the canonical product (the one used to describe all the other products, as we saw in the implementation of triple and quad), either is the canonical sum. The Yocaml.Data.Validation.either validator is very similar to the Yocaml.Data.Validation.pair validator. It takes two other validators and applies the first in the case of left, the second in the case of right:

# let int_or_string = V.(either int string) ;;
val int_or_string : D.t -> (int, string) Either.t V.validated_value = <fun>

Let's look at how it's used, first with the Left int case:

# int_or_string D.(either int string (Either.left 10)) ;;
- : (int, string) Either.t V.validated_value = Ok (Either.Left 10)

Let's try the Right string case:

# int_or_string D.(either int string (Either.right "foo")) ;;
- : (int, string) Either.t V.validated_value = Ok (Either.Right "foo")

No surprise, now let's look at a validation error, trying to validate an option as an either, to understand the representation of sums, under the hood:

# int_or_string D.(option string (Some "foo")) ;;
- : (int, string) Either.t V.validated_value =
Error
 (V.Invalid_shape
   {V.expected = "Left <abstr> | Right <abstr>";
    given = Yocaml.Data.String "foo"})

by trying to validate an option as an either doesn't give us much information about how sums are represented, but it does tell us that the validator seems to be quite aware of the different constructors that can be envisaged for a sum.

In fact, like pairs, Yocaml.Data uses an internal representation of constructors that respects this form: {"constr": constr_key; value: Yocaml.Data.t}. This makes it possible to build validators for arbitrary sums, without having to build a trick à la pair/triple/quad, using Yocaml.Data.Validation.sum. Let's try to build a validator for the following type...unnecessarily complicated:

type a_complicated_type =
  | Aaf
  | Bcwrz of int * float
  | Krups of string option
  | Kalco of (bool, string) Either.t
  | Piou of float list
  | Xxxx of string * int * (int list option)
  | Zzzz

First, let's build a function to easily lift values from our complicated type to Yocaml.Data.t. This demonstrates the symmetrical representation of the sum to "build" data:

let a_complicated_type  =
  let open Yocaml.Data in
  sum (function
    | Aaf             -> "aaf",   null
    | Bcwrz (a, b)    -> "bcwrz", pair int float (a, b)
    | Krups x         -> "krups", option string x
    | Kalco x         -> "kalco", either bool string x
    | Piou  x         -> "piou",  list_of float x
    | Xxxx  (a, b, c) -> "xxxx",  triple string int (option @@ list_of int) (a, b, c)
    | Zzzz            -> "zzzz",  null
  )

It's the responsibility of the person building the represented sum to choose the representation of each constructor (and unfortunately, nothing is enforced) but as YOCaml is a static site generator, we assume that the consistency between produced and verified constructors live in the same repo, and are easy to check.

Writing a validator for this type is largely similar to writing the projection function. We will construct a list which associates a constructor (a string) with a validation function:

# let validate_complicated_type  =
    let open Yocaml.Data.Validation in
    let the_long_triple =
      triple string int (option @@ list_of int)
    in
    sum [
      "aaf",   null               $ (fun () -> Aaf)
    ; "bcwrz", pair int float     $ (fun (a, b) -> Bcwrz (a, b))
    ; "krups", option string      $ (fun x -> Krups x)
    ; "kalco", either bool string $ (fun x -> Kalco x)
    ; "piou",  list_of float      $ (fun x -> Piou x)
    ; "xxxx",  the_long_triple    $ (fun (a, b, c) -> Xxxx (a, b, c))
    ; "zzzz",  null               $ (fun () -> Zzzz)
    ] ;;
val validate_complicated_type :
  D.t -> a_complicated_type Yocaml.Data.Validation.validated_value = <fun>

We can see the symmetry, the $ operator is just an alias on map, which allows, once the branch has been validated, to project it into the correct constructor. Let's construct a value, via our previous function (which should therefore, by default, be valid) and play with our validation function!

# V.list_of (validate_complicated_type) (
     D.list_of a_complicated_type [
       Zzzz
     ; Aaf
     ; Piou [1.2; 54.89]
     ; Bcwrz (42, 24.42)
     ; Kalco (Either.Left true)
     ; Krups None
     ; Krups (Some "Foo Bar")
     ; Xxxx ("hello", 10, Some [1234; 87665])
     ]
  ) ;;
- : a_complicated_type list V.validated_value =
Ok
 [Zzzz; Aaf; Piou [1.2; 54.89]; Bcwrz (42, 24.42); Kalco (Either.Left true);
  Krups None; Krups (Some "Foo Bar"); Xxxx ("hello", 10, Some [1234; 87665])]

And just out of curiosity, let's try to validate an unacceptable value!

# validate_complicated_type (D.int 64) ;;
- : a_complicated_type Yocaml.Data.Validation.validated_value =
Error
 (Yocaml.Data.Validation.Invalid_shape
   {Yocaml.Data.Validation.expected =
     "Aaf <abstr> | Bcwrz <abstr> | Krups <abstr> | Kalco <abstr> | Piou <abstr> | Xxxx <abstr> | Zzzz <abstr>";
    given = Yocaml.Data.Int 64})

And let's observe an invalid constructor, we learn more about the representation of constructors:

# validate_complicated_type (D.sum (function _ -> "arf", D.int 10) []) ;;
- : a_complicated_type Yocaml.Data.Validation.validated_value =
Error
 (Yocaml.Data.Validation.Invalid_shape
   {Yocaml.Data.Validation.expected =
     "Aaf <abstr> | Bcwrz <abstr> | Krups <abstr> | Kalco <abstr> | Piou <abstr> | Xxxx <abstr> | Zzzz <abstr>";
    given =
     Yocaml.Data.Record
      [("constr", Yocaml.Data.String "arf"); ("value", Yocaml.Data.Int 10)]})

The validation of the sums is a little less secure than one might hope because they do not rely solely on invariants described by the AST of Yocaml.Data, and ask the user to define the representation of constructors, this is why we recommend relying as much as possible on generic representations like either to deal with sums.

But yes, the declaration/validation module allows the expression and validation of arbitrary sums and as the description of the sum is based on pattern matching and arbitrary identifiers, the sums also make it possible to encode sums "encoded with objects or records" (erg) or polymorphic variants.

Create a low-level validator

Even if it seems to us that the combinators presented are sufficient to generically describe key-value structures, as, although private, the AST is not abstract, it is perfectly possible to create your own validator using pattern matching, and the function Yocaml.Data.Validation.fail_with can be used to propagate an error. For example, let's implement a validator that only accepts booleans true:

# let only_true = function
    | Yocaml.Data.Bool true -> Ok ()
    | other ->
        Yocaml.Data.Validation.fail_with
           ~given:"Not a true value"
           "the value has to be true"
  ;;
val only_true : D.t -> unit Yocaml.Data.Validation.validated_value = <fun>

We may be surprised that the given argument is a character string, but this is to allow the developer of a validator to choose the mode of representation of the observed structure. But hey, as there are validators for all the roots of the AST, the previous function is rewritten in terms of combinations.

You can also extend the Yocaml.Data.Validation.custom_error type and use the Yocaml.Data.Validation.fail_with_custom function to build specific validation pipelines with precise handling of additional errors.

Fine-grained validators

For the moment, we've mainly seen validators that transform Yocaml.Data.t values into regular OCaml values. We also sketched out a slightly richer form of composition using the $ operator, which allowed us to apply a function to the valid result of a validator.

The Infix module, which is included in Yocaml.Data.Validation, offers several small operators for building richer, more precise validation functions:

  • Yocaml.Data.Validation.Infix Infix operators are essentially used to compose data validators (unlike binding operators, which are used to compose record validation fragments).

The operators described in this module can be used to manage three different scenarios: mapping, sequential application and alternative.

Mapping

Mapping is the most obvious: it applies a function to the result of a validation sequence. If, for example, I want to validate an integer, but want to convert it to a string, I can easily use $:

# V.(int $ string_of_int) (D.int 23) ;;
- : string V.validated_value = Ok "23"

We used $ to transform a validated value and project it into the desired constructor.

sequential application

Sequential application, using the & operator, can be summarized as executing a first validator, and then executing a second one, passing it the result of the first. For example, in the Yocaml.Data.Validation module, there are a number of utility functions that validate data fragments, here are just a few of them: Yocaml.Data.Validation.positive, Yocaml.Data.Validation.equal, Yocaml.Data.Validation.where.

Let's build a validator that validates only even positive integers :

let positive_and_even =
    let open Yocaml.Data.Validation in
    int & positive & where (fun x -> x mod 2 = 0)

Let's try it with an integer that doesn't respect the expectation:

# positive_and_even (D.int (-23)) ;;
- : int Yocaml.Data.Validation.validated_value =
Error
 (Yocaml.Data.Validation.With_message
   {Yocaml.Data.Validation.given = "-23"; message = "should be positive"})

Let's try it with an integer that doesn't respect the expectation for other reason:

# positive_and_even (D.int 25) ;;
- : int Yocaml.Data.Validation.validated_value =
Error
 (Yocaml.Data.Validation.With_message
   {Yocaml.Data.Validation.given = "*"; message = "unsatisfied predicate"})

And let's finally try it with a valid integer!

# positive_and_even (D.int 24) ;;
- : int Yocaml.Data.Validation.validated_value = Ok 24

The sequential application lets you chain validators to build validation pipelines.

Alternatives

Alternatives, represented by the / operator, can be used to execute a second validator if the first has failed. For example, let's imagine this scenario, I want to retrieve a string of characters or an integer that I consider to be a string of characters:

let my_v =
  let open Yocaml.Data.Validation in
  string / (int $ string_of_int)

And it can be used with const in the event of absolute valis failure :

# V.(my_v / const "erf") (D.string "Hello") ;;
- : string V.validated_value = Ok "Hello"
# V.(my_v / const "erf") (D.int 1234) ;;
- : string V.validated_value = Ok "1234"
# V.(my_v / const "erf") D.(list_of string ["Hello"]) ;;
- : string V.validated_value = Ok "erf"

With the support of alternatives, we've seen all the ways to build increasingly expressive validators, enabling us to capture as many scenarios as possible to describe metadata.

Executing preconditions/postconditions

In some cases, you may want to build data under certain conditions. You can use the let* operator to describe pre/post-conditions. For example, let's modify our user validation function to allow validation only if registrations are open:

let user_validation registration_open user =
  let open Yocaml.Data.Validation in
  let* () =
     if registration_open then Ok ()
     else fail_with ~given:"false" "registration are closed"
  in
  record (fun fields ->
    let+ username = required fields "username" string
    and+ age = required fields "age" int
    and+ nouns = optional_or  ~default:[] fields "nouns" (list_of string)
    and+ email = optional fields "email" string
    in
      { username; age; nouns; email }
  ) user

If you use validation with registration open, validation behaves correctly:

# user_validation true D.(record [
    "username", string "JohnDoe42"
  ; "age", int 42
  ; "nouns", list_of string ["he"; "him"; "his"; "himself"]
  ; "email", string "jdoe@name.com"
  ]) ;;
- : (user, V.value_error) result =
Result.Ok
 {username = "JohnDoe42"; age = 42; nouns = ["he"; "him"; "his"; "himself"];
  email = Some "jdoe@name.com"}

But if you close the registrations, the validation will fail (without executing the record validation):

# user_validation false D.(record [
    "username", string "JohnDoe42"
  ; "age", int 42
  ; "nouns", list_of string ["he"; "him"; "his"; "himself"]
  ; "email", string "jdoe@name.com"
  ]) ;;
- : (user, V.value_error) result =
Result.Error
 (Yocaml.Data.Validation.With_message
   {Yocaml.Data.Validation.given = "false";
    message = "registration are closed"})

We can also describe preconditions that construct values on which a ‘next’ validation sequence will depend (and performing postcondition). Here, we will assume that we want the user to provide confirmation of their name, which must be equal to the username they have provided:

let user_validation registration_open user =
  let open Yocaml.Data.Validation in
  let* validated_user =
    record (fun fields ->
      let+ username = required fields "username" string
      and+ age = required fields "age" int
      and+ nouns = optional_or  ~default:[] fields "nouns" (list_of string)
      and+ email = optional fields "email" string
      in
        { username; age; nouns; email }
    ) user
  in
  let* () =
    record (fun fields ->
      let+ _ =
        required fields "username_confirmation"
          (string
             & equal ~equal:String.equal
                ~pp:Format.pp_print_string
                validated_user.username)
      in ()
     ) user
  in Ok validated_user

If our confirmation is correct, the validation process will run smoothly!

# user_validation true D.(record [
    "username", string "JohnDoe42"
  ; "age", int 42
  ; "nouns", list_of string ["he"; "him"; "his"; "himself"]
  ; "email", string "jdoe@name.com"
  ; "username_confirmation", string "JohnDoe42"
  ]) ;;
- : (user, V.value_error) result =
Result.Ok
 {username = "JohnDoe42"; age = 42; nouns = ["he"; "him"; "his"; "himself"];
  email = Some "jdoe@name.com"}

On the other hand, if the confirmation is wrong:

# user_validation true D.(record [
    "username", string "JohnDoe42"
  ; "age", int 42
  ; "nouns", list_of string ["he"; "him"; "his"; "himself"]
  ; "email", string "jdoe@name.com"
  ; "username_confirmation", string "JohnDoe43"
  ]) ;;
- : (user, V.value_error) result =
Result.Error
 (Yocaml.Data.Validation.Invalid_record
   {Yocaml.Data.Validation.errors =
     Yocaml__.Nel.(::)
      (Yocaml.Data.Validation.Invalid_field
        {Yocaml.Data.Validation.given = Yocaml.Data.String "JohnDoe43";
         field = "username_confirmation";
         error =
          Yocaml.Data.Validation.With_message
           {Yocaml.Data.Validation.given = "JohnDoe43";
            message = "should be equal to JohnDoe42"}},
       []);
    given =
     [("username", Yocaml.Data.String "JohnDoe42");
      ("age", Yocaml.Data.Int 42);
      ("nouns",
       Yocaml.Data.List
        [Yocaml.Data.String "he"; Yocaml.Data.String "him";
         Yocaml.Data.String "his"; Yocaml.Data.String "himself"]);
      ("email", Yocaml.Data.String "jdoe@name.com");
      ("username_confirmation", Yocaml.Data.String "JohnDoe43")]})

In some cases, dependent validation makes it possible to construct increasingly complex situations, so it should only be used when really necessary.

OCaml

Innovation. Community. Security.