Try   HackMD

Monomorphic Uses

Our first usecase comes directly from Jacques Garrigue's paper introducing polymorphic variants to OCaml.

As a reminder, the "polymorphic" in "polymorphic variant" refers to row polymorphism, meaning that a polymorphic variant's type is parameterized over an open row of tags, enabling extensibility. This is a form of parametric polymorphism, where parametricity relates to rows and allows a polymorphic variant to potentially include additional tags beyond those explicitly specified. This is a separate concept to how ordinary variants and polymorphic variants can carry parametrically polymorphic payloads.

Therefore, when we say that polymorphic variants can be used in monomorphic contexts, we are saying that polymorphic variants can be useful in contexts that do not take advantage of row polymorphism. This is a common usecase for polymorphic variants and does not require a developer to predeclare a variant type.

The following is an implementation of a function using ordinary variants:

# type color = Red | Green | Blue;;
type color = Red | Green | Blue

# let describe_color (c : color) =
    match c with
    | Red -> "It's red"
    | Green -> "It's green"
    | Blue -> "It's blue";;
val describe_color : color -> string = <fun>

# let descr_1 = describe_color Red;;
val descr_1 : string = "It's red"

We can use polymorphic variants in the same way, avoiding its row polymorphic capabilities by explicitly adding an upper bound to make the polymorphic variant type expression closed:

# let describe_poly_color c =
    match c with
    | `Red -> "It's red"
    | `Green -> "It's green"
    | `Blue -> "It's blue"
val describe_poly_color : [< `Blue | `Green | `Red ] -> string = <fun>

# let poly_descr_1 = describe_poly_color `Red;;
val poly_descr_1 : string = "It's red"

# let poly_descr_2 = describe_poly_color `Yellow;;
Error: This expression has type [> `Yellow ]
       but an expression was expected of type [< `Blue | `Green | `Red ]
       The second variant type does not allow tag(s) `Yellow

When we pass it an argument outside of its bounds, we receive an error.

Note: Even if describe_poly_color specified c as an argument of an open polymorphic type and we never passed it an argument with a type outside the set of tags explicitly permitted, the function can be considered monomorphic.

Overloaded Tags

Our second usecase also comes directly from Jacques Garrigue's paper. The example in the paper is converted and expanded from pseudocode to OCaml.

A common usecase for polymorphic variants is when our codebase benefits from the ability of polymorphic variant tags to be overloaded, meaning that the tags can be reused across different functions in combination with tags that are specialized to different contexts:

Imagine we are writing a graphics library that

type entry_index =
  | Anchor
  | At of int
  | End
  | Insert
  | Num of int
  | Selfirst
  | Sellast

type listbox_index =
  | Active
  | Anchor
  | AtXY of int * int
  | End
  | Num of int

type menu_index =
  | Active
  | At of int
  | End
  | Last
  | None
  | Num of int
  | Pattern of string

let entry_index (w: entrywidget) (idx: entry_index) : int =
  match idx with
  | Anchor -> (* Handle anchor *) 0
  | At i -> i
  | End -> 1
  | Insert -> 2
  | Num i -> i
  | Selfirst -> 3
  | Sellast -> 4

let listbox_index (w: listboxwidget) (idx: listbox_index) : int =
  match idx with
  | Active -> 0
  | Anchor -> 1
  | AtXY (x, y) -> x + y
  | End -> 2
  | Num i -> i

let menu_index (w: menuwidget) (idx: menu_index) : int =
  match idx with
  | Active -> 0
  | At i -> i
  | End -> 1
  | Last -> 2
  | None -> -1
  | Num i -> i
  | Pattern s -> String.length s

The above example requires duplication of constructors; Anchor, At of int, End, Num of int, and Active are referenced in more than one ordinary variant. These similar constructors must be redefined for each datatype because we cannot use the same constructors across types, so we must define separate types.

Polymorphic variants allow constructors to exist independently of any specific type, eliminating duplication and allowing flexible reuse:

let entry_index (w: entrywidget)
      (idx: [ `Anchor | `At of int | `End | `Insert | `Num of int | `Selfirst | `Sellast ]) : int =
  match idx with
  | `Anchor -> 0
  | `At i -> i
  | `End -> 1
  | `Insert -> 2
  | `Num i -> i
  | `Selfirst -> 3
  | `Sellast -> 4

let listbox_index (w: listboxwidget)
      (idx: [ `Active | `Anchor | `AtXY of int * int | `End | `Num of int ]) : int =
  match idx with
  | `Active -> 0
  | `Anchor -> 1
  | `AtXY (x, y) -> x + y
  | `End -> 2
  | `Num i -> i

let menu_index (w: menuwidget)
      (idx: [ `Active | `At of int | `End | `Last | `None | `Num of int | `Pattern of string ]) : int =
  match idx with
  | `Active -> 0
  | `At i -> i
  | `End -> 1
  | `Last -> 2
  | `None -> -1
  | `Num i -> i
  | `Pattern s -> String.length s

Because polymorphic variants do not require predeclaration, there is no need to duplicate types. The previously duplicate constructors (Anchor, At, End, Num, and Active) can be reused across different functions. This is called overloading. Overloading means reusing the same tag across different functions or types without explicitly defining multiple distinct types.

Thus, polymorphic variants provide overloaded constructors that adapt to different contexts while avoiding redundancy and rigid type constraints.

Composing with Result

For the following example, we will use the Result module from the OCaml Standard Library, which is automatically opened in every module. You can read more about Result and its use in error handling in our guide on error handling.

The Result type in OCaml is defined as:

type ('a, 'b) result = Ok of 'a | Error of 'b

However, we can use polymorphic variants to make error handling more flexible. Below are two examples demonstrating the use of ordinary variants and polymorphic variants using result in a compositional context.

# type ov_err =
   | Index_out_of_bounds
   | Not_even;;
type ov_err = Index_out_of_bounds | Not_even

# type ('a, 'ov_err) result = Ok of 'a | Error of 'ov_err;;
type ('a, 'ov_err) result = Ok of 'a | Error of 'ov_err

# let ov_safe_nth lst n result =
    if n < 0 || n >= List.length lst
    then Error Index_out_of_bounds
    else Ok (List.nth lst n);;
val ov_safe_nth : 'a list -> int -> ('a, ov_err) result = <fun>

# let ov_double_if_even x =
    if x mod 2 = 0
    then Ok (x * 2)
    else Error Not_even;;
val double_if_even : int -> (int, ov_err) result = <fun>

# let ov_bind r f =
    match r with
    | Ok v -> f v
    | Error e -> Error e;;
val ov_bind : ('a, 'b) result -> ('a -> ('c, 'b) result) -> ('c, 'b) result =
  <fun>

# let ov_process_list lst idx =
    ov_bind (ov_safe_nth lst idx)
            (fun x -> ov_double_if_even x);;
val ov_process_list : int list -> int -> (int, ov_err) result = <fun>

# ov_process_list [2; 3; 4] 0;;
- : (int, ov_err) result = Ok 4

# ov_process_list [2; 3; 4] 1;;
- : (int, ov_err) result = Error Not_even

 # ov_process_list [2; 3; 4] 5;;
- : (int, ov_err) result = Error Index_out_of_bounds

Notice that we must first declare two ordinary variant types (ov_err and ('a, 'ov_err) result) in order to use them them with our functions. We then define two functions (ov_safe_nth and ov_double_if_even) that are composed together in ov_process_list using ov_bind.

Note: These examples demonstrate a method of composing functions together in a way that manages arguments embedded in a context. In this case, the context is in a result type, but similar implementations exist for contexts such as option, map, and many other data structures in OCaml's Standard Library. A function that handles this kind of composition is called bind, meaning that it binds two functions together in a compositional chain. Another term for this kind of composition is monadic, which is derived from category theory.

Now lets convert the above example to use polymorphic variants:

# let pv_safe_nth lst n =
    if n < 0 || n >= List.length lst
    then Error `Index_out_of_bounds
    else Ok (List.nth lst n);;
val pv_safe_nth : 'a list -> int -> ('a, [> `Index_out_of_bounds ]) result = <fun>

# let double_if_even x =
    if x mod 2 = 0
    then Ok (x * 2)
    else Error `Not_even;;
val pv_double_if_even : int -> (int, [> `Not_even ]) result = <fun>

# let pv_bind r f =
    match r with
    | Ok v -> f v
    | Error e -> Error e;;
val pv_bind : ('a, 'b) result -> ('a -> ('c, 'b) result) -> ('c, 'b) result =
  <fun>

# let pv_process_list lst idx =
    pv_bind (pv_safe_nth lst idx)
            (fun x -> double_if_even x);;
val pv_process_list :
  int list -> int -> (int, [> `Index_out_of_bounds | `Not_even ]) result =
  <fun>

# pv_process_list [2; 3; 4] 0;;
- : (int, [> `Index_out_of_bounds | `Not_even ]) result = Ok 4

# pv_process_list [2; 3; 4] 1;;
- : (int, [> `Index_out_of_bounds | `Not_even ]) result = Error `Not_even

# pv_process_list [2; 3; 4] 5;;
- : (int, [> `Index_out_of_bounds | `Not_even ]) result = Error `Index_out_of_bounds

Transitioning from Ordinary to Polymorphic Variants in an API

In this usecase, we will demonstrate a web API where an endpoint returns different response types. We will demonstrate a common practice where a developer first uses polymorphic variants as an API matures. When the API becomes stable, the code is converted to use ordinary variants.

Suppose we have a function that makes an API request and handles different outcomes. Since the structure is simple, we use polymorphic variants for quick iteration.

 # let fetch_user_1 user_id =
     match user_id with
     | 1 -> `Ok "Alice"
     | 2 -> `Ok "Bob"
     | _ -> if Random.bool () then `NotFound else `ServerError;;
val fetch_user_1 : int -> [ `NotFound | `Ok of string | `ServerError ] = <fun>

# let process_fetch_1 fetch_call =
    match fetch_call with
    | `Ok name -> Printf.sprintf "User found: %s\n" name
    | `NotFound -> Printf.sprintf "User not found\n"
    | `ServerError -> Printf.sprintf "Internal server error\n";;
val process_fetch_1 : [< `NotFound | `Ok of string | `ServerError ] -> string = <fun>

# process_fetch_1 (fetch_user_1 3);;
- : string = "Internal server error\n"

When fetching a user, we simulate an error by randomly selecting between \NotFoundand`ServerError`.

Thanks to polymorphic variants, there is no need to define a type, we simply return different cases. It is also flexible because we can add new cases without changing any type definitions.

At this time, we believe our API is not yet stable, so we will continue using polymorphic variants. Sure enough, we soon discover that the API is incomplete and we want it to handle an error message.

# let fetch_user_2 user_id =
    match user_id with
    | 1 -> `Ok "Alice"
    | 2 -> `Ok "Bob"
    | _ -> if Random.bool ()
           then `Error `NotFound
           else `Error (`ServerError "DB connection failed");;
val fetch_user_2 :
  int -> [> `Error of [> `NotFound | `ServerError of string ] | `Ok of string ] = <fun>

# let process_fetch_2 fetch_call =
    match fetch_call with
    | `Ok name -> Printf.sprintf "User found: %s\n" name
    | `Error `NotFound -> Printf.sprintf "User not found\n"
    | `Error (`ServerError msg) -> Printf.sprintf "Server error: %s\n" msg;;
val process_fetch_2 :
  [< `Error of [< `NotFound | `ServerError of string ] | `Ok of string ] -> unit = <fun>

# process_fetch_2 (fetch_user_2 3);;
Server error: DB connection failed
- : unit = ()

This change is simple because nested errors (Error of [ ... ]) are easy to add without changing global type definitions.

At this point, we decide that our API is stable, so we can now convert our polymorphic variants to ordinary variants to lock down the API's behavior.

type api_error =
  | NotFound
  | ServerError of string

type api_response =
  | Ok of string
  | Error of api_error

let fetch_user_v3 (user_id : int) : api_response =
  match user_id with
  | 1 -> Ok "Alice"
  | 2 -> Ok "Bob"
  | _ -> if Random.bool () then Error NotFound else Error (ServerError "DB connection failed")

(* Example usage *)
let () =
  match fetch_user_v3 3 with
  | Ok name -> Printf.sprintf "User found: %s\n" name
  | Error NotFound -> Printf.sprintf "User not found\n"
  | Error (ServerError msg) -> Printf.sprintf "Server error: %s\n" msg

As a rule of thumb, it is a good idea to switch to ordinary variants when multiple functions use the same set of response types and the behavior of our functions is well defined.

A central declaration ensures consistency. It is also easier to handle errors involving ordinary variants. Additionally, code written with ordinary variants tends to be easier to read an interpret than code using polymorphic variants.

Polymorphic Variants with Phantom Types

Phantom types enhance compile-time type safety without incurring runtime performance costs because they exist solely at the type level and do not influence the program's runtime behavior. By introducing additional type parameters that are not utilized in the actual data representation, phantom types allow the compiler to enforce stricter type checks during compilation. This ensures that certain kinds of errors are caught early in the development process, leading to more robust and reliable code. Since these type parameters do not translate into actual data fields or affect the memory layout of data structures, they impose no additional overhead during program execution.

Imagine a API for files where we prevent misuse like reading from a closed file:

# type 'a file = { file_descriptor: int } (* a phantom type *)
type 'a file = { file_descriptor : int; }

# let open_file path : [> `Open] file =
    { file_descriptor = 42 };;
val open_file : 'a -> [> `Open ] file = <fun>

# let close_file (f : [> `Open] file) : [> `Closed] file =
    { file_descriptor = -1 };;
val close_file : [> `Open ] file -> [> `Closed ] file = <fun>

# let read_file (f : [> `Open] file) : string =
    "This is the content of a simulated file";;
val read_file : [> `Open ] file -> string = <fun>

# let f = open_file "test.txt" in
  let _ = read_file f in
  let _ = close_file f in
    ();;
- : unit = ()

Here, 'a is a phantom type parameter because it does not correspond to any value within the file record. It exists only to carry compile-time information about the file's state.

The types open_state and closed_state are defined as polymorphic variants representing the possible states of a file. These are used as markers for the phantom type parameter 'a in the file type.

The function open_file returns a file with its phantom type parameter indicating that the file is in the open state.

Functional Reactive Programming (FRP) with Polymorphic Variants

In FRP (functional reactive programming), events can originate from multiple sources (UI, sensors, network, and etc.), and polymorphic variants enable structural typing, avoiding redundant type declarations.

Imagine that we model an event stream (Signal.t):

# module Signal = struct
    type 'a t = (unit -> 'a)  (* Simple event source *)

    let map f s = fun () -> f (s ())
    let merge s1 s2 = fun () -> if Random.bool () then s1 () else s2 ()
  end;;
module Signal :
  sig
    type 'a t = unit -> 'a
    val map : ('a -> 'b) -> (unit -> 'a) -> unit -> 'b
    val merge : (unit -> 'a) -> (unit -> 'a) -> unit -> 'a
  end
# type ui_event = [ `Click of int | `KeyPress of char ]
  type sensor_event = [ `Temperature of float | `MotionDetected ];;
type ui_event = [ `Click of int | `KeyPress of char ]
type sensor_event = [ `MotionDetected | `Temperature of float ]

# let ui_source =
    fun () -> if Random.bool () then `Click 42 else `KeyPress 'a';;
val ui_source : ui_event Signal.t = <fun>

# let sensor_source =
    fun () -> if Random.bool () then `Temperature 22.5 else `MotionDetected;;
val sensor_source : sensor_event Signal.t = <fun>

# let combined_source : [> ui_event | sensor_event ] Signal.t =
    Signal.merge ui_source sensor_source;;
val combined_source :
  [> `Click of int
   | `KeyPress of char
   | `MotionDetected
   | `Temperature of float ]
  Signal.t = <fun>

# let handle_event (event : [> ui_event | sensor_event]) =
  match event with
  | `Click x -> Printf.printf "Button clicked: %d\n" x
  | `KeyPress c -> Printf.printf "Key pressed: %c\n" c
  | `Temperature t -> Printf.printf "Temperature: %.1f\n" t
  | `MotionDetected -> Printf.printf "Motion detected!\n";;
val handle_event :
  [ `Click of int | `KeyPress of char | `MotionDetected | `Temperature of float
  ] -> unit = <fun>

# let event = combined_source () in
    handle_event event;;
Button clicked: 42
- : unit = ()

Encoding HTML in Hierarchical Structures

With ordinary variants, defining a type for HTML elements might look like this:

# type html_element =
    | Heading of int * string
    | Paragraph of string
    | Div of html_element list
    | Span of html_element list;;
type html_element =
    Heading of int * string
  | Paragraph of string
  | Div of html_element list
  | Span of html_element list

This keeps our HTML data structure flat by combining all elements into a single ordinary variant type.

With this unified type, a single rendering function can handle all elements:

# let rec render_html = function
    | Paragraph text -> "<p>" ^ text ^ "</p>"
    | Span elements -> "<span>" ^
                       (String.concat ""
                         (List.map render_html elements)) ^
                       "</span>"
    | Heading (level, text) -> "<h" ^ string_of_int level ^ ">" ^
                               text ^
                               "</h" ^ string_of_int level ^ ">"
    | Div elements -> "<div>" ^
                      (String.concat ""
                        (List.map render_html elements)) ^
                      "</div>";;
val render_html : html_element -> string = <fun>

Here, html_element is an ordinary variant type. To add new elements like Img, we must modify the original type definition and potentially all functions that pattern match on html_element. This rigidity hampers extensibility and code reuse.

To make our code more modular and reusable, we can decompose our data structure like so:

# type basic_html =
   | Paragraph of string
   | Span of basic_html list;;
type basic_html = Paragraph of string | Span of basic_html list

# type heading_html =
   | Basic of basic_html
   | Heading of int * string;;
type heading_html = Basic of basic_html | Heading of int * string

# type extended_html =
   | Heading of heading_html
   | Div of extended_html list;;
type extended_html = Heading of heading_html | Div of extended_html list

In the above, we define a base type basic_html for fundamental HTML elements. Next, we extend this with a heading_html type that includes headings. Finally, we define an extended_html type that incorporates all previous elements and adds the Div element:

With these types defined, we can implement the rendering functions for each level of our hierarchy:

# let rec render_basic = function
   | Paragraph text -> "<p>" ^ text ^ "</p>"
   | Span elements -> "<span>" ^
                     (String.concat ""
                       (List.map render_basic elements)) ^
                     "</span>";;
val render_basic : basic_html -> string = <fun>

# let rec render_heading = function
   | Basic basic -> render_basic basic
   | Heading (level, text) -> "<h" ^ string_of_int level ^ ">" ^
                             text ^
                             "</h" ^ string_of_int level ^ ">";;
val render_heading : heading_html -> string = <fun>

# let rec render_extended = function
   | Heading heading -> render_heading heading
   | Div elements -> "<div>" ^
                    (String.concat ""
                      (List.map render_extended elements)) ^
                    "</div>";;
val render_extended : extended_html -> string = <fun>

At this point, implementing our functions on our ordinary variants becomes challenging to due to the nested nature of our variant types. The extended_html type encapsulates heading_html, which in turn encapsulates basic_html. This nesting requires careful pattern matching to correctly render each element.

This example illustrates the limitations of using ordinary variants for representing structures like HTML. The lack of subtyping makes it difficult to write flexible and reusable functions, as each function must account for the entire hierarchy of types. Polymorphic variants, with their support for subtyping, offer a more elegant solution by allowing functions to operate on subsets of variants, thereby promoting code reuse and extensibility:

# type basic_html = [
   | `Paragraph of string
   | `Span of basic_html list
  ];;
type basic_html = [ `Paragraph of string | `Span of basic_html list ]

# type heading_html = [
   | basic_html
   | `Heading of int * string
  ];;
type heading_html =
    [ `Heading of int * string
    | `Paragraph of string
    | `Span of basic_html list ]

# type extended_html = [
   | heading_html
   | `Div of extended_html list
  ];;
type extended_html =
    [ `Div of extended_html list
    | `Heading of int * string
    | `Paragraph of string
    | `Span of basic_html list ]

This structure allows us to create functions that operate on specific subsets of HTML elements. For example:

# let rec render_basic = function
   | `Paragraph text -> "<p>" ^ text ^ "</p>"
   | `Span elements -> "<span>" ^
                       (String.concat ""
                         (List.map render_basic elements)) ^
                       "</span>";;
val render_basic :
  ([< `Paragraph of string | `Span of 'a list ] as 'a) -> string = <fun>

# let render_heading = function
   | #basic_html as e -> render_basic e
   | `Heading (level, text) -> "<h" ^ string_of_int level ^ ">" ^
                               text ^
                               "</h" ^ string_of_int level ^ ">";;
val render_heading :
  [< `Heading of int * string | `Paragraph of string | `Span of basic_html list
  ] -> string = <fun>

# let rec render_extended = function
   | #heading_html as e -> render_heading e
   | `Div elements -> "<div>" ^
                      (String.concat ""
                        (List.map render_extended elements)) ^
                      "</div>";;
val render_extended :
  ([< `Div of 'a list
    | `Heading of int * string
    | `Paragraph of string
    | `Span of basic_html list ]
   as 'a) ->
  string = <fun>

This approach showcases subtyping, since our functions can accept any value that is a subtype of their expected type. For instance, render_heading can process both basic_html and heading_html elements, promoting code reuse and modularity.

In summary, polymorphic variants with subtyping in OCaml provide a powerful mechanism to model complex, hierarchical data structures like HTML, offering greater flexibility and scalability compared to ordinary variants.

Special thanks to garrigue, ninjaaron, orbitz, bluddy, alan, rand, gasche, Gopiandcode