Mixin objects.

Alain Frisch

The “O” part of OCaml is not very popular amongst OCaml developers and many of them explain (with some pride) that they avoid any contact with the OO sublanguage altogether.

In this post, I’ll try to restore the image of classes and objects in OCaml by showing some interesting use cases for them. And I won’t even mention the obvious and typical use of objects in GUI frameworks! (Doh, I just did it!)

Let’s assume one wants to model a variety of different business concepts of a given domain as OCaml types. I’ll take “financial instruments” as examples, because this is the domain of expertise of LexiFi, but the examples won’t even mention our generic approach to describing the semantics of financial contracts (our “contract algebra”). Each instrument will be described by an OCaml data type storing its parameters. Let’s define the parameters for a simple instrument:

(* Some global mocked-up definition *)
type date = int
type underlying = string
let fixing (_ : underlying) (_ : date) = 0.
   (* A function which returns the value observed on the market,
      on a given date, for a given underlying. *)

(* The parameters for a capital protected instrument *)
type capital_protected =
  {
    start_date: date;
    end_date: date;
    underlying: underlying;
    participation: float;
    notional: float;
  }

This instrument is assumed to pay on end_date a cash flow whose amount is obtained from the following:

  • We define “final_performance” as the ratio between the value of the underlying on the end_date and its value on the start_date, minus 1.

  • The paid amount is the notional if the final performance is negative, and “notional + participation * final_performance” otherwise.

We can write a function which computes the list of cash flows (as list of pairs (payment_date, amount)) for this instrument:

let cash_flows_of_capital_protected
  {
   start_date;
   end_date;
   underlying;
   participation;
   notional;
  } =
  let final_performance =
    fixing underlying end_date /. fixing underlying start_date -. 1.
  in
  [ (end_date,
     notional *. (1. +. max 0. (participation *. final_performance))) ]

Returning several results

But maybe we are interested in also getting the final_performance, for reporting purposes. To avoid code duplication, we can do:

let final_performance_of_capital_protected
   {start_date; end_date; underlying; _} =
  fixing underlying end_date /. fixing underlying start_date -. 1.

let cash_flows_of_capital_protected
   ({end_date; participation; notional; _} as params) =
  let final_performance = final_performance_of_capital_protected params in
  [ (end_date,
     notional *. (1. +. max 0. (participation *. final_performance))) ]

This is not very nice, because we loose the static check that all parameters are indeed used (warning 27). For instance, if we forget to bind (and use) the participation field, we get no warning from the compiler. Another solution is to return both the cash flows and the final performance together. While we are at it, let’s also return the initial and final values of the underlying:

let capital_protected
 {start_date; end_date; underlying; participation; notional} =
  let initial_value = fixing underlying start_date in
  let final_value = fixing underlying end_date in
  let final_performance = final_value /. initial_value -. 1. in
  let cash_flows =
    [ (end_date,
       notional *. (1. +. max 0. (participation *. final_performance))) ]
  in
  initial_value, final_value, final_performance, cash_flows

But now, if we are only interested in computing the final_performance, we also end up computing the cash flows, which, in a more complex example, might be costly or even impossible (the computation could raise an exception). With objects, we could write:

let capital_protected
  {
   start_date;
   end_date;
   underlying;
   participation;
   notional;
  } =
  object(this)
    method initial_value = fixing underlying start_date
    method final_value = fixing underlying end_date

    method final_performance =
      (this # final_value) /. (this # initial_value) -. 1.

    method cash_flows =
      [ (end_date,
         notional *. (1. +. max 0. (participation *. (this # final_performance)))) ]
  end

Contrary to using a tuple or records to return the various “results”, we get the following advantages from using objects:

  • Only the results which are requested are actually computed.

  • If more results have to be returned, this won’t usually change the call sites.

  • Because of the nominal nature of objects, it is possible to write polymorphic functions which can operate on the objects created by different instruments, as long as they all define the required methods.

An an illustration of the last point, the function below works on any instrument defining final_value and cash_flows.

let show o =
  Printf.printf "Final value: %f\n" (o # final_value);
  Printf.printf "Number of cash flows: %i\n" (List.length (o # cash_flows))

The astute reader will remark that in the example above, if we want to get both the final_value and the final_performance, the final_value method will be called twice, resulting in duplicated computation. Using a variant of the code in this blog post, let’s define:

let memoize_obj (o : < .. >) =
  let o = Obj.repr o in
  let meths = Obj.dup (Obj.field o 0) in
  Obj.set_field o 0 meths;
  let nmeths : int = Obj.magic (Obj.field meths 0) in
  for i = 0 to nmeths - 1 do
    let idx = i * 2 + 2 in
    let old_f : Obj.t -> Obj.t = Obj.magic (Obj.field meths idx) in
    let memo = lazy (old_f o) in
    let new_f self = if self == o then Lazy.force memo else old_f self in
    Obj.set_field meths idx (Obj.repr new_f);
  done

class memoized = object(this)
  initializer memoize_obj this
end

I won’t go into the details, but the effect of inheriting from this class (with an empty interface) is that the resulting object gets a “memoized” semantics for its methods. So let’s add inherit memoized to the capital_protected object above, and we’re done: the returned object will evaluate each of its method at most once.

Sharing common behavior

Now let’s assume that the end_date can be specified either explicitly or as a shift from the start_date:

type from_start_date = [`Explicit of date | `N_days_after_start_date of int]

type capital_protected =
  {
    start_date: date;
    end_date: from_start_date;
    underlying: underlying;
    participation: float;
    notional: float;
  }

let capital_protected
 {
  start_date;
  end_date;
  underlying;
  participation;
  notional;
 } =
  object(this)
    inherit memoized
    method end_date =
      match end_date with
      | `Explicit t -> t
      | `N_days_after_start_date n -> start_date + n

    method initial_value = fixing underlying start_date
    method final_value = fixing underlying (this # end_date)

    method final_performance =
      (this # final_value) /. (this # initial_value) -. 1.

    method cash_flows =
      [ (end_date,
         notional *. (1. +. max 0. (participation *. (this # final_performance)))) ]
  end

If we have other instruments with both a start_date and an end_date, it is likely that they will share the same logic to compute the actual end_date. So we would like to factorise this piece of code. With objects, this can be done like that:

class virtual end_date_from_start_date end_date =
  object(this)
    method virtual start_date: date
    method end_date =
      match end_date with
      | `Explicit t -> t
      | `N_days_after_start_date n -> this # start_date + n
  end

let capital_protected
 {
  start_date;
  end_date;
  underlying;
  participation;
  notional;
 } =
  object(this)
    inherit memoized
    inherit end_date_from_start_date end_date
    method start_date = start_date
    method initial_value = fixing underlying (this # start_date)
    method final_value = fixing underlying (this # end_date)

    method final_performance =
      (this # final_value) /. (this # initial_value) -. 1.

    method cash_flows =
      [ (this # end_date,
         notional *. (1. +. max 0. (participation *. (this # final_performance)))) ]
  end

We have introduced a reusable “end_date_from_start_date” class. It could be used in another instrument which has the same logic for defining the actual end_date. Note how the “start_date” is passed to this virtual class, not as a parameter, but as a virtual method. This kind of class is often referred to as a “mixin”.

Let’s introduce some more such reusable classes:

(* mixin for products with a notional *)
class notional (x : float_ =
  object
    method notional = x
  end

(* mixin for products with a start date *)
class start_date (x : date) =
  object
    method start_date = x
  end

(* mixin for products with a single underlying *)
class single_underlying (x : underlying) =
  object
    method value_on = fixing x
  end

(* mixin for performance products *)
class virtual performance_product =
  object(this)
    method virtual start_date: date
    method virtual end_date: date
    method virtual value_on: date -> float

    method initial_value = this # value_on (this # start_date)
    method final_value = this # value_on (this # end_date)
    method final_performance =
      this # final_value /. this # initial_value -. 1.
  end

(* mixin for products with a single final cash flow
   obtained by scaling a payoff formula by a notional *)
class virtual final_payoff =
  object(this)
    method virtual end_date: date
    method virtual notional: float
    method virtual product_formula: float
    method cash_flows =
      [ (this # end_date,
         (this # notional) *. (this # product_formula)) ]
  end

let capital_protected {start_date; end_date; underlying; participation; notional} =
  object(this)
    inherit memoized
    inherit end_date_from_start_date end_date
    inherit performance_product
    inherit final_payoff
    inherit notional notional
    inherit single_underlying underlying
    inherit start_date start_date
    method product_formula =
      1. +. max 0. (participation *. (this # final_performance))
  end

The plumbing is quite light: since the start_date value is passed as a method, it is available for the two reusable classes which require it (end_date_from_start_date and performance_product); and the end_date produced by one class is available to the two other classes which require it. And now, we can easily define other instruments which reuse some or all of these classes. For instance, one can define a variant of the capital_protected with a cap:

type capital_protected_with_cap =
  {
    start_date: date;
    end_date: from_start_date;
    underlying: underlying;
    participation: float;
    notional: float;
    cap: float;
  }

let capital_protected_with_cap {start_date; end_date; underlying; participation; notional; cap} =
  object(this)
    inherit memoized
    inherit end_date_from_start_date end_date
    inherit performance_product
    inherit final_payoff
    inherit notional notional
    inherit single_underlying underlying
    inherit start_date start_date
    method product_formula =
      1. +. max 0. (min cap (participation *. (this # final_performance)))
  end

Since the “capital_protected” and the “capital_protected_with_cap” both inherit from the same mixins, we could have created a “meta mixin” simply combining all these mixins (or a subset):

class vanilla_product ~start_date ~end_date ~underlying ~notional =
  object
    inherit memoized
    inherit end_date_from_start_date end_date
    inherit performance_product
    inherit final_payoff
    inherit notional notional
    inherit single_underlying underlying
    inherit start_date start_date
  end

let capital_protected {start_date; end_date; underlying; participation; notional} =
  object(this)
    inherit vanilla_product ~start_date ~end_date ~underlying ~notional
    method product_formula =
      1. +. max 0. (participation *. (this # final_performance))
  end

let capital_protected_with_cap {start_date; end_date; underlying; participation; notional; cap} =
  object(this)
    inherit vanilla_product ~start_date ~end_date ~underlying ~notional
    method product_formula =
      1. +. max 0. (min cap (participation *. (this # final_performance)))
  end

Let’s create another variant where the notional is derived from the initial value of the underlying:

type capital_protected_unit =
  {
    start_date: date;
    end_date: from_start_date;
    underlying: underlying;
    participation: float;
  }

let capital_protected_unit {start_date; end_date; underlying; participation} =
  object(this)
    inherit memoized
    inherit end_date_from_start_date end_date
    inherit performance_product
    inherit final_payoff
    inherit single_underlying underlying
    inherit start_date start_date
    method notional = this # initial_value
    method product_formula =
      1. +. max 0. (min participation *. (this # final_performance))
  end

And yet another variant where the performance is based on a basket of underlyings. Since this notion of basket is quite common in many instruments, we can again factorise its support in a reusable class:

type capital_protected_basket =
{
  start_date: date;
  end_date: from_start_date;
  underlyings: (float * underlying) list;
  participation: float;
  notional: float;
}

class virtual basket composition =
object(this)
  method virtual start_date: date
  method value_on t =
    List.fold_left (fun x (w, u) -> x +. w *. fixing u t /. fixing u (this # start_date)) 0. composition
  method basket_size = List.length composition
end

let capital_protected_basket {start_date; end_date; underlyings; participation; notional} =
object(this)
  inherit memoized
  inherit end_date_from_start_date end_date
  inherit performance_product
  inherit final_payoff
  inherit basket underlyings
  inherit notional notional
  inherit start_date start_date
  method product_formula =
    1. +. max 0. (participation *. (this # final_performance))
end

Yet another example of an Asian call, paying the arithmetic average of the underlying observed on several dates, minus a strike, floored at 0. The notion of Asian product (= arithmetic average) being quite common, we can factorise it:

type asian_call =
{
  underlying: underlying;
  fixing_dates: date list;
  end_date: date;
  strike: float;
  notional: float;
}

class virtual asian dates =
object(this)
  method virtual value_on: date -> float
  method average = List.fold_left (+.) 0. (List.map (this # value_on) dates)
                   /. float (List.length dates)
end

let asian_call_basket {underlying; fixing_dates; end_date; strike; notional} =
object(this)
  inherit memoized
  inherit final_payoff
  inherit asian fixing_dates
  inherit single_underlying underlying
  inherit notional notional
  method end_date = end_date
  method product_formula = max 0. (this # average -. strike)
end

Note that for this example, we have decided to make the end_date explicit again (because there is no start_date). And now, we can create an “Asian call” on a basket of underlying performances:

type asian_call_basket =
{
  underlyings: (float * underlying) list;
  fixing_dates: date list;
  start_date: date;
  end_date: from_start_date;
  strike: float;
  notional: float;
}

let asian_call_basket {underlyings; fixing_dates; start_date; end_date; strike; notional} =
object(this)
  inherit memoized
  inherit final_payoff
  inherit asian fixing_dates
  inherit basket underlyings
  inherit end_date_from_start_date end_date
  inherit start_date start_date
  inherit notional notional
  method product_formula = max 0. (this # average -. strike)
end

This is a bit lengthy, but it illustrates a possible approach to organise a library of similar “things” sharing some common concepts, and from which we need to derive some attributes, using common formulas. By abstracting such common computations into reusable classes, and passing information around through (virtual) methods, a lot of the required plumbing comes from free.

A nice property of factorising the code like that is that it becomes very lightweight to add more attributes. For instance, we can extend the performance_product mixin to return the “current” value and performance (between the start_date and a global “today” reference):

class virtual performance_product =
object(this)
  method virtual start_date: date
  method virtual end_date: date
  method virtual value_on: date -> float

  method initial_value = this # value_on (this # start_date)
  method final_value = this # value_on (this # end_date)
  method final_performance =
    this # final_value /. this # initial_value -. 1.

  method current_value = this # value_on !today
  method current_performance =
    (this # current_value /. this # initial_value) -. 1
end

All the instruments which inherit from this mixin gets the two new attributes, without any extra plumbing.

The examples above are a bit tedious, because the factorised computations are simple enough that we don’t gain a lot by sharing same, but I hope they convey the idea. If you try to write the same examples, with the same amount of code sharing, without objects, you’ll end up with some very tedious code which does mostly plumbing (passing data to functions, extracting their result from record or tuple fields).