package primavera

  1. Overview
  2. Docs
Dependency injection based on a Reader Monad

Install

dune-project
 Dependency

Authors

Maintainers

Sources

primavera-1.0.0.tbz
sha256=cde900d727ed27b623ccb978ab1b0695dd049cd26de387104ecc0495773abe2c
sha512=6b4ff15f0750ca9ea9941c875e4c4ddd5d65de8b0ecb8fd018a9ef2994316fd7ad82642dc5849372dc703a8ab0707f905e30b9434cb69c64f693e2f455009696

doc/primavera/Primavera/index.html

Module PrimaveraSource

As mentioned in the following article, sometimes the trivial ways of abstracting effects or dependencies in OCaml offer ‘too much power’ (type construction through modules or continuation control for effects).

The goal of Primavera is to provide an approach compatible with inference to control its dependencies by taking advantage of OCaml's type inference and using objects.

This approach, although more limited than effects and modules, allows operations to be captured as handlers using row polymorphism of objects.

Identity

Primavera is built on top of an identity monad to abstract dependencies whose normal form is a regular value.

Types

Sourcetype 'a output = 'a

The type of expression that dependency injection must produce.

Sourcetype ('a, 'handler) t

The type that describes a calculation that uses dependency injection. 'a is the normal form of the programme and 'handler is the object that describes the set of dependencies.

Running and performing

Sourceval run : handler:'handler -> ('a -> ('b, 'handler) t) -> 'a -> 'b output

Performs a computation with a given handler.

Sourceval perform : ('handler -> 'a output) -> ('a, 'handler) t

Convert a regular function (which takes an handler) into an performable effect.

Regular functions

Sourceval return : 'a -> ('a, 'e) t

return x lift x in the context of the type t.

Sourceval map : ('a -> 'b) -> ('a, 'e) t -> ('b, 'e) t

map f x mapping from f over x. Lift a function from 'a -> 'b to a function from 'a t -> 'b t.

Sourceval apply : ('a -> 'b, 'e) t -> ('a, 'e) t -> ('b, 'e) t

apply f x given f and x apply f on x.

Sourceval bind : ('a, 'e) t -> ('a -> ('b, 'e) t) -> ('b, 'e) t

bind x f sequentially apply f on x.

Sourceval replace : 'a -> ('b, 'handler) t -> ('a, 'handler) t

replace x comp discard the result of comp by x.

Sourceval ignore : ('a, 'handler) t -> (unit, 'handler) t

ignore comp same as regular ignore function but for effectful computation.

Sourceval zip : ('a, 'handler) t -> ('b, 'handler) t -> ('a * 'b, 'handler) t

zip a b is the monoidal product between a and b.

Sourceval join : (('a, 'handler) t, 'handler) t -> ('a, 'handler) t

join comp flatten the result of comp.

Sourceval compose : ('a -> ('b, 'handler) t) -> ('c -> ('a, 'handler) t) -> 'c -> ('b, 'handler) t

compose f g x is the kleisli composition of f and g.

Sourceval map2 : ('a -> 'b -> 'c) -> ('a, 'handler) t -> ('b, 'handler) t -> ('c, 'handler) t

map2 lift a function 2-arity function.

Sourceval map3 : ('a -> 'b -> 'c -> 'd) -> ('a, 'handler) t -> ('b, 'handler) t -> ('c, 'handler) t -> ('d, 'handler) t

map3 lift a function 3-arity function.

Sourceval map4 : ('a -> 'b -> 'c -> 'd -> 'e) -> ('a, 'handler) t -> ('b, 'handler) t -> ('c, 'handler) t -> ('d, 'handler) t -> ('e, 'handler) t

map4 lift a function 4-arity function.

Sourceval map5 : ('a -> 'b -> 'c -> 'd -> 'e -> 'f) -> ('a, 'handler) t -> ('b, 'handler) t -> ('c, 'handler) t -> ('d, 'handler) t -> ('e, 'handler) t -> ('f, 'handler) t

map5 lift a function 5-arity function.

Infix Operators

Sourcemodule Infix : sig ... end

Infix operators.

Binding Operators

Sourcemodule Syntax : sig ... end

Bindings operators.

Included operators

Sourceval (<$>) : ('a -> 'b) -> ('a, 'handler) t -> ('b, 'handler) t

f <$> x is map f x (infix version of map)

Sourceval (<$) : 'a -> ('b, 'handler) t -> ('a, 'handler) t

a <$ x is replace a x (infix version of replace)

Sourceval ($>) : ('a, 'handler) t -> 'b -> ('b, 'handler) t

x $> a is replace a x (infix (flipped) version of replace)

Sourceval (<*>) : ('a -> 'b, 'handler) t -> ('a, 'handler) t -> ('b, 'handler) t

f <*> x is apply f x (infix version of apply)

Sourceval (<&>) : ('a, 'handler) t -> ('b, 'handler) t -> ('a * 'b, 'handler) t

a <&> b is zip a b (infix version of zip)

Sourceval (<*) : ('a, 'handler) t -> ('b, 'handler) t -> ('a, 'handler) t

a <* b Perform a and b but discard b.

Sourceval (*>) : ('a, 'handler) t -> ('b, 'handler) t -> ('b, 'handler) t

a *> b Perform a and b but discard a.

Sourceval (<<) : ('a, 'handler) t -> ('b, 'handler) t -> ('a, 'handler) t

a << b Sequentially perform a following by b but discard b.

Sourceval (>>) : ('a, 'handler) t -> ('b, 'handler) t -> ('b, 'handler) t

a >> b Sequentially perform a following by b but discard a.

Sourceval (>>=) : ('a, 'handler) t -> ('a -> ('b, 'handler) t) -> ('b, 'handler) t

m >>= f is bind m f (infix version of bind)

Sourceval (=<<) : ('a -> ('b, 'handler) t) -> ('a, 'handler) t -> ('b, 'handler) t

f =<< m is bind m f (infix (flipped) version of bind)

Sourceval (<=<) : ('a -> ('b, 'handler) t) -> ('c -> ('a, 'handler) t) -> 'c -> ('b, 'handler) t

f <=< g is compose f g (infix version of compose)

Sourceval (>=>) : ('a -> ('b, 'handler) t) -> ('b -> ('c, 'handler) t) -> 'a -> ('c, 'handler) t

f >=> g is compose g f (infix (flipped) version of compose)

Sourceval (let+) : ('a, 'handler) t -> ('a -> 'b) -> ('b, 'handler) t

let+ x = m in f x is map (fun x -> f x) m.

(binding version of map)

Sourceval (and+) : ('a, 'handler) t -> ('b, 'handler) t -> ('a * 'b, 'handler) t

let+ x = m and+ y = n in f x y is map (fun (x, y) -> f x y) (zip m n).

(binding version of zip)

Sourceval (let*) : ('a, 'handler) t -> ('a -> ('b, 'handler) t) -> ('b, 'handler) t

let* x = m in f x is bind m (fun x -> f x).

(binding version of bind)

Sourceval (and*) : ('a, 'handler) t -> ('b, 'handler) t -> ('a * 'b, 'handler) t

let* x = m and* y = n in f x y is bind (zip m n) (fun (x, y) -> f x y).

(binding version of zip)

Requirements

module Req : sig ... end

The requirements describe the minimum interfaces for building Primavera instances on parameterised types (of arity 1 or 2). They broadly follow the minimal interface of a Functor, an Applicative and a Monad.

Building a Reader

Sourcemodule Make : sig ... end

Example

As is often the case, to demonstrate abstraction of effects or dependency injection, we use the usual teletype example. A programme capable of interacting with the console to print and read.

We begin by describing all possible interactions in our programme, the primitives read_line and print in an Fx module using the function Primavera.perform:

  module Fx = struct
    open Primavera

    let print message = perform (fun handler -> handler#print message)
    let print_line message = print (message ^ "\n")
    let read_line () = perform (fun handler -> handler#read_line)
  end

The handler passed via the Primavera.perform function is used to call one of its methods (and allow inference to track the operations that can be executed).

We can observe the signature of our module to understand how operations propagate through the type system.

  # #show_module Fx;;
  module Fx :
    sig
      val print : 'a -> ('b, < print : 'a -> 'b; .. >) Primavera.t
      val print_line : string -> ('a, < print : string -> 'a; .. >) Primavera.t
      val read_line : unit -> ('a, < read_line : 'a; .. >) Primavera.t
    end

Now that we have our operations, we can use them to describe the ancient teletype programme! To do this, we use the let* (Primavera.bind) operator to sequence operations with effects.

  let teletype () =
    let open Primavera in
    let* () = Fx.print_line "What is your name?" in
    let* name = Fx.read_line () in
    Fx.print_line ("Hello " ^ name)
  ;;

If we inspect the type of our teletype programme, we can observe several things:

  # let t = teletype ;;
  val t :
    unit ->
    (unit, < print : string -> unit; read_line : string; .. >) Primavera.t =
    <fun>

A primavera programme generally takes the following form: 'input -> ('outpout, <set_of_operation; ..> t).

Here, we can see that our programme takes unit and returns unit, and that it propagates the following operations:

  • print which takes a string and returns unit
  • read_line which returns a string.

Now that we have described a programme, we need to execute it, providing concrete implementations for the operations that can be propagated, using Primavera.run and giving an object to the flag handler:

    # Primavera.run
       ~handler:object
         method print message =
           print_string message

           (* Here we hook the call of read_line to
              works in test-context  *)
           method read_line =
            "Xavier"
        end
       teletype
       ()
    What is your name?
    Hello Xavier
    - : unit = ()