Crazy OCaml dynamic evaluation: is this legal (defined behaviour)?

Note: this is part of some code I’m writing for a research project, so don’t worry about such insanity somehow floating into actual production code :wink: .

I’ve been recently working on a project wherein, for various reasons, I have been needing to type-check and evaluate dynamically generated OCaml code at runtime (and possibly even let that generated code interact with modules in the host context). By looking at the code of the native toplevel and with some help from the compiler-libs, I have managed to do this :tada: ! (hint, it involves using the compiler to compile the code down to a library, and then dynamically linking it to the current executable).

For the purposes of this post, the exact implementation with which I have done this is probably not that important, but we can summarise the high level interface to this dynamic execution capabilities with the following signature:

type env

val raw_parse_str: string -> Parsetree.structure
(** [raw_parse_str txt] uses the OCaml compiler to parse a given string into structure AST. *)

val raw_parse_expr_str: string -> Parsetree.expression
(** [raw_parse_expr_str txt] uses the OCaml compiler to parse a given string into expression AST. *)

val initial_env: unit -> env
(** [initial_env ()] returns an initial OCaml typing environment,
   preloaded with the OCaml stdlib.  *)

val dyn_load_definition_as_module: env -> mod_name:string -> ast:Parsetree.structure -> env
(** [dyn_load_definition_as_module env ~mod_name ~ast] compiles and
    dynamically loads/evaluates the AST [ast] under the module name
    [mod_name], returning an updated [env] *)

val eval_expr: env -> Parsetree.expression -> 'a
(** [eval_expr env expr] compiles and evaluates the expression
    [expr] and returns the value.

    NOTE: The return type of this function is 'a (any type at
    all). You must explicitly annotate the return type at any call
    site, otherwise be prepared for possible memory corruption. *)

If people are interested, I can also share the implementation of this module, but for now, it’s not that relevant.

For context, in my application, I have expressions that roughly follow the following structure:

type expr = [
    `App of string * expr list
  | `Int of int
  | `Var of string
]

Each such reified term represents a particular test returning a boolean value, and may contain free variables that are only in scope within the context of a larger expression. For each such expression, I map it to an OCaml ast, include it within a larger expression with the appropriate variables, and evaluate the resulting AST using the library above to retrieve the boolean result:

(* initial test *)
let test = `App ("=", [`App ("Array.length", [`Var "a"]); `Var "i"])

(* surrounding context *)
let ctx =
   let a = [| 1; 2; 3; 4 |] in
   let i = 10 in
   (??)

(* resulting OCaml expression *)
let a = [| 1; 2; 3; 4 |] in
let i = 10 in
Array.length a = i

This actually works quite well and reliably for the most part, save for one small problem: each evaulation involves running the compiler to build a library, and importantly dynamically linking it into the current executable. After several thousand or more evaluations, the dynamic linking seems to fail, I’m guessing because the kernel just gave up and wasn’t written expecting programs to dynamically load so many libraries.

I have found a (hacky) solution.

Because my expression language is a small subset of OCaml, I can generate a bespoke expression interpreter for a given evaluation context as follows (note how the evaluation of variables are deferred to an environment object passed in):

let eval = fun env expr ->
  let rec eval_expr env : _ -> Wrap.wrap = function[@warning "-8"]
    | `Var "a" -> MkWrap (env#a)
    | `Var "i" -> MkWrap (env#i)
    | `App ("Array.length", [ls]) -> MkWrap (Array.length (Wrap.unwrap (eval_expr env ls)))
    | `App ("+", [l; r]) -> MkWrap ((Wrap.unwrap (eval_expr env l)) + (Wrap.unwrap (eval_expr env r)))
    | `App ("=", [l; r]) -> MkWrap ((Wrap.unwrap (eval_expr env l)) = (Wrap.unwrap (eval_expr env r)))
    | `Int i -> MkWrap i in
  (Wrap.unwrap @@ eval_expr env expr : bool)

Where, Wrap.wrap and Wrap.unwrap are a module defined as follows:

module Wrap = struct
   type wrap = MkWrap : 'a -> wrap 
   let unwrap (MkWrap a) = Obj.magic a
end

I can then combine this with the outer specification to get a self-contained expression that I only need to compile once, but can be used to test as many reified computations as I want:

fun expr ->
let a = [| 1; 2; 3; 4 |] in
let i = 10 in
eval (object method a = a method i = i end) expr

Running this actually seems to work exactly as I expect (the expressions I generate are guaranteed to be well-typeable? by construction).

So, my question for the OCaml community is: is this legal/defined behaviour? (assuming my expressions are well typed, and no other shenanigans are in play)

Of course, no one should actually use this in production code, but it’s a fun little trick I suppose

We were talking about something tangentially related, me and a couple of friends came across it, just something I wanted to share: without Obj.magic you can still structurally compare and hash Dyn fields directly because the polymorphic prims to do so work on the runtime structure of those types. Something you’re doing a level up I suppose in OCaml instead of C:

module Untyped = struct
  type t = Dyn : 'a -> t
  let compare = compare
  let equal = (=)
  let hash = Hashtbl.hash
end
module CursedMap = Map.Make(Untyped)
module CursedTbl = Hashtbl.Make(Untyped)

and then all the functions work as expected e.g.

let open Untyped in
CursedMap.(empty
  |> add (Dyn "answer") 42
  |> add (Dyn 4) 20
  |> add (Dyn 1.25) 5
  |> find (Dyn 4)
)
1 Like

Oh, yeah, that’s also cool, using polymorphic comparisons with existential types is a pretty nice? trick, although I guess you’ve got to be wary of the structural representation of your values:

let result v =
  let open CursedMap in
  empty
  |> add (Dyn v) "hello"
  |> find_opt (Dyn None)

let print_opt x =
  print_endline @@ "received " ^
  match x with
  | None -> "None"
  | Some v -> "Some " ^ v

let () =
  print_opt (result 1);         (* received None *)
  print_opt (result 0);         (* received Some "hello" *)
  print_opt (result []);        (* received Some "hello" *)
  print_opt (result ())         (* received Some "hello" *)

I don’t understand why you are going through the trouble of dynamically compiling if the end result is an eval interpretation? (you could just call eval from the host program, there is no performance benefit from compiling eval dynamically)

Anyway, the MkWrap constructor doesn’t provide you any more safety than let wrap = Obj.magic and unwrap x = x which is obviously pretty bad!.. Have you considered GADTs to proove that your expressions are indeed well-typed?

(* an expression of type 'a, expecting a variable environment 'env *)
type ('env, 'a) ast =
  | Int : int -> ('env, int) ast
  | Var_a : (< a : 'a ; .. >, 'a) ast
  | Var_i : (< i : 'a ; .. >, 'a) ast
  | Eq : (_, 'a -> 'a -> bool) ast
  | Array_length : (_, 'a array -> int) ast
  | Apply : ('env, 'a -> 'b) ast * ('env, 'a) ast -> ('env, 'b) ast

let rec eval : type env a. env -> (env, a) ast -> a
= fun env -> function
  | Int i -> i
  | Var_a -> env#a
  | Var_i -> env#i
  | Eq -> ( = )
  | Array_length -> Array.length
  | Apply (f, x) -> (eval env f) (eval env x)

let test = Apply (Apply (Eq, Apply (Array_length, Var_a)), Var_i)

;;

eval (object method a = [|1;2;3|] method i = 3 end) test

Ah yes, good question - there is a good reason for that, although I guess given that I’ve simplified the examples for this post, it probably doesn’t show that well.

The reason for dynamically compiling is because the outer context (which is also dynamically generated) may contain arbitrarily complex OCaml code - it is only the singular expression at the end which I can guarantee has a simple structure:

fun expr ->
let a = (* arbitrarily complex OCaml code returning an array *) in
let i = 10 in
eval (object method a = a method i = i end) expr

Rather than having to write an interpreter for the entirety of OCaml, I can write an interpreter for just the simple test expressions, and leave the evaluation of the other parts to the compiler libs.

Yes, naturally GADTs were a possible choice that I considered, however, the main problem is that the expression context itself (i.e the a and i variables themselves) is dynamically generated. Indeed, I could also dynamically generate the type itself as well I suppose, but that means I’d still have the challenge of writing an validator that converts from my untyped expr type to the typed ('env,'a) ast, which in-itself would probably also require some kind of existential wrapper as well.

Given that I’m already assuming that the expressions are well typed, it seemed rather pointless to go through the extra rigamarole of building this GADT encoding and evaluator just to be able to allow the expressions to be well typed (especially since all of this code itself is dynamically generated, so the types aren’t really that helpful, beyond just serving as an extra validation of the generation scheme)

Ha the perils of simplifying! In your last example, the call to eval ... expr is still tailcall, so it looks like you could dynamically compile and compute the constants:

let a = (* arbitrarily complex OCaml code returning an array *) in
let i = 10 in
(a, i)

And then eval dynamic_values expr from the host program (with no need to recompute a for each new expression). But I’m guessing that expr could be used in a more complex way by the context, in which case it still looks simpler not to embed eval in the dynamically compiled program, but rather use a function to represent the expression:

fun (expr : int array * int -> bool) ->
  while true do
    let a = (* arbitrarily complex OCaml code *) in
    let i = 10 in
    expr (a, i) (* no `eval` here! *)
  done

And you can then call this from the host by passing the lambda (fun env -> eval env expr). To me it looks a lot harder to dynamically compile eval alongside the context, as you need to ensure that the expr of the dynamic and host program have the same memory layout (… is this why you used a polymorphic variant?)

1 Like

Haha, yes indeed, you seem to have recovered parts of the problem I’m running into here, despite the simplified examples I’ve given.

The problem with this approach is that I don’t know at compile time what the evaluation context will look like. Hence, for an arbitrary user input, I can’t give a proper type to the result of evaluating this expression. Sure, for the example I’ve given, you can say that the input is a function that takes a tuple, but in general, it’s going to take some n-ary tuple, with types that will be dependent on what is in the context. This then leads to problems, because it leads me back to the problem that each possible assertion that I want to run the code with will need to be dynamically compiled as well, and then we’re right back at the problem of a hard limit of the number of dynamic libraries that I can load into my executable.

If we generate a bespoke interpreter (of type env -> expr -> bool ) instead, then we can get around this constraint, because we can assign a single type to the outer context (that of (expr -> bool) -> bool).

Yes, exactly! For slightly more context, the larger problem I’m looking at is trying to insert generated assertions into (somewhat-)arbitrary user-provided OCaml code (hence the evaluation context itself is not known ahead of time - I can’t guarantee that only variables i and a will be in the context, if at all for that matter). Further, I need to run the user provided code with multiple (thousands+) possible assertions, and these assertions don’t necessarily need to be in tail call position, hence the slightly more complex approach I’ve taken here.

Hm well what’s the type definition of env? Haha wait, are you procedurally generating those lines in the dynamic eval:

    | `Var "a" -> MkWrap (env#a)
    | `Var "i" -> MkWrap (env#i)

Such that the predicates can then get access to the arbitrary variables that they expect from the env? Then the problem is still not the full blown eval, but only the dispatching of the variables’ values from their names. Perhaps this would work with some more Obj.magic on the host when calling the env dispatch function:

type whatever

fun expr ->
  (* ... *)
  expr (function | "a" -> Obj.magic a
                 | "i" -> Obj.magic i
                 | _   -> (assert false : whatever))

Anyway this is getting all too crazy for me, I wish you good luck! (I’m not sure I agree that the environment has to be so freeform, I understand that it is convenient to skip some of the static analysis, but you might discover that Obj.magic is unspecified if you keep using it)


I would love to know why the dynamic loading eventually crashes when you use it too much though :slight_smile:

Haha, yes, exactly - I was planning on generating a custom evaluation function each time I had a new evaluation context, however…

Good point - thanks for the pointer - you’re entirely correct, the use of an object for the environment is actually pretty overkill. I guess I can write a single evaluator function in the host context, no dynamic evaluation, and just defer handling environment variables to it.

I’m curious if anyone in the OCaml community could give some more advice on this.

@Gopiandcode Any chance you have a demo about your dynamic compiler?

The whole project itself is not available online yet, although hopefully it will be soon.

In the meantime, I can probably release the subcomponent that I use to dynamically build and link code, although I’m fairly busy for the next few weeks, so I’ll try and do this when I manage to catch some free time (maybe next week).