[ocaml-ctypes] Best practices for wrapping ocaml-ctypes?

Jeremy Yallop yallop at gmail.com
Mon Aug 17 11:24:13 BST 2015


I thought I'd rejig the conversions a bit and put together a complete
working example.

First, the value type definition from an earlier message:

   type value =
      Null
    | True
    | FloatValue of float
    | StringValue of string
    | AtomValue of string
    | BuiltinFunctionValue of (value -> value)

Next, a module for converting back and forth between Emily values and
OCaml values.  This combines the two conversions that you currently
store in the 'valueToCFn' and 'cToValueFn' types.

  module Conversion :
  sig
     type 'a t
     (** A value of type 'a t' can be used to convert between
         the types 'value' and 'a' *)

     val val_of : 'a t -> ('a -> value)
     val of_val : 'a t -> (value -> 'a)

     val float : float t
     (** Conversions for floats *)

     val (^->) : 'a t -> 'b t -> ('a -> 'b) t
     (** Conversions for functions *)
  end =
  struct
    type 'a t = { val_of: 'a -> value;
                  of_val: value -> 'a }

    (* If you're not keen on puns, you can write
       'let val_of c = c.val_of' etc. instead *)
    let val_of {val_of} = val_of
    let of_val {of_val} = of_val

    let value_of_float f = FloatValue f

    let float_of_value = function
      | FloatValue f -> f
      | _ -> failwith "Expected float"

    let float = { val_of = value_of_float;
                  of_val = float_of_value }

    let value_of_function arg ret f =
       BuiltinFunctionValue (fun x -> val_of ret (f (of_val arg x)))

    let function_of_value arg ret = function
      | BuiltinFunctionValue f -> (fun x -> of_val ret (f (val_of arg x)))
      | _ -> failwith "Expected function"

    let (^->) arg ret = { val_of = value_of_function arg ret;
                          of_val = function_of_value arg ret }
  end

(I've chosen '^->' for the Conversion.t function value because
operators beginning with '^' associate right, so 'x ^-> y ^-> z' means
'x ^-> (y ^-> z)' rather than '(x ^-> y) ^-> z', just as in the
corresponding OCaml function types.)

Here's the conversion module in action:

   # Conversion.(of_val (float ^-> float));;
   - : value -> float -> float = <fun>
   # Conversion.(val_of (float ^-> float));;
   - : (float -> float) -> value = <fun>
   # Conversion.(val_of (float ^-> float ^-> float));;
   - : (float -> float -> float) -> value = <fun>
   # Conversion.(of_val ((float ^-> float) ^-> float));;
   - : value -> (float -> float) -> float = <fun>

Let's use these conversions to write the general function that binds C
functions using Ctypes and exposes them to Emily.  The following two
types play a similar role to valueToCFn etc., combining a type
representation and a conversion function:

   type ty = Ty : 'a Ctypes.typ * 'a Conversion.t -> ty
   type fn = Fn : ('a -> 'b) Ctypes.fn * ('a -> 'b) Conversion.t -> fn

Here's the analogue of your 'typeConvert' function:

   let typeConvert = function
       "float" -> Ty (Ctypes.float, Conversion.float)
     | _ -> failwith "??"

Next comes a slightly irritating part.  Since 'Foreign.foreign'
doesn't support nullary functions the base case for binding is the one
argument function type.  So for a function with arguments 'a', 'b',
'c' and 'd' and return type 'e' we'll need to to build an initial
function specification from 'd' and 'e', then fold in the other
argument types ('a', 'b', 'c').  Towards that goal here's a function
which splits a list into its initial elements and last element:

   (* 'a list -> 'a list * 'a *)
  let split_last l =
  let rec loop aux = function
      [] -> invalid_arg "split_last"
    | [x] -> List.rev aux, x
    | x :: xs -> loop (x :: aux) xs
  in loop [] l

  # split_last ['a'; 'b'; 'c'; 'd'];;
  - : char list * char = (['a'; 'b'; 'c'], 'd')

We now have all the bits we need to write the binding function.  The
following builds type representations and conversions in parallel,
then combines them at the end, like your 'valueForeignUnary':

  (* val functionFrom : string -> string list -> string -> value *)
  let functionFrom name args returning =
    let args, last_arg = split_last args in
    let Ty (rty, r) = typeConvert returning in
    let Ty (aty, a) = typeConvert last_arg in
    let Fn (fnty, fn) = List.fold_right
      (fun arg (Fn (fty, f)) ->
        let Ty (tty, t) = typeConvert arg in
        Fn (Ctypes.(tty @-> fty), Conversion.(t ^-> f)))
      args
      (Fn (Ctypes.(aty @-> returning rty), Conversion.(a ^-> r)))
    in Conversion.val_of fn (Foreign.foreign name fnty)

In order to test it'll be helpful to have an 'apply' function:

   (* val ( $ ) : value -> value -> value *)
   let ($) f p = match f with
       BuiltinFunctionValue f -> f p
     | _ -> failwith "Application of non-function"

Here's an example of using 'functionFrom' to call a unary function
from the C standard library:

   # let expf = functionFrom "expf" ["float"] "float";;
   val expf : value = BuiltinFunctionValue <fun>
   # expf $ FloatValue 1.0;;
   - : value = FloatValue 2.71828174591064453

And here's a call to a binary function:

   # let powf = functionFrom "powf" ["float"; "float"] "float";;
   val powf : value = BuiltinFunctionValue <fun>
   # powf $ FloatValue 2.0 $ FloatValue 3.0;;
   - : value = FloatValue 8.

I hope that helps, but feel free to follow up on anything that's unclear!

Kind regards,

Jeremy.


More information about the Ctypes mailing list