Ppxlib: Getting the original definition of `typ_constr` like `type_declaration` from `core_type` of `ptyp_constr`

I’m currently learning using ppxlib to write ppx deriver, and I found this tutorial. Here’s an example of automatically generating a stringify function:

let rec expr_of_type typ =
  let loc = typ.ptyp_loc in
  match typ with
  | [%type: int] -> [%expr string_of_int]
  | [%type: string] -> [%expr fun i -> i]
  | [%type: bool] -> [%expr string_of_bool]
  | [%type: float] -> [%expr string_of_float]
  | [%type: [%t? t] list] ->
      [%expr
        fun lst ->
          "["
          ^ List.fold_left
              (fun acc s -> acc ^ [%e expr_of_type t] s ^ ";")
              "" lst
          ^ "]"]
  | _ ->
      Location.raise_errorf ~loc "No support for this type: %s"
        (string_of_core_type typ)

let generate_impl ~ctxt (_rec_flag, type_decls) =
  let loc = Expansion_context.Deriver.derived_item_loc ctxt in
  List.map
    (fun typ_decl ->
      match typ_decl with
      | { ptype_kind = Ptype_abstract; ptype_manifest; _ } -> (
          match ptype_manifest with
          | Some t ->
              let stringify = expr_of_type t in
              let func_name =
                if typ_decl.ptype_name.txt = "t" then { loc; txt = "stringify" }
                else { loc; txt = typ_decl.ptype_name.txt ^ "_stringify" }
              in
              [%stri let [%p Pat.var func_name] = [%e stringify]]
          | None ->
              Location.raise_errorf ~loc "Cannot derive anything for this type"
          )
      | _ -> Location.raise_errorf ~loc "Cannot derive anything for this type")
    type_decls

This deriver can be used like:

type i_list = int list [@@deriving stringify]

type b_list = bool list [@@deriving stringify]

type i_list_list = int list list [@@deriving stringify]

let () =
  let i_lst = [ 1; 2; 3 ] in
  let b_lst = [ true; false; true ] in
  let i_lst_lst = [ [ 1; 2; 3 ]; [ 4; 5; 6 ] ] in
  print_endline (i_list_stringify i_lst);
  print_endline (b_list_stringify b_lst);
  print_endline (i_list_list_stringify i_lst_lst)

However, it does not support types with type alias, for example.

type i_list = int list 
type i_list_list = i_list list [@@deriving stringify] (* does not work *)

I checked the documentation for OCaml AST used in ppxlib, and found that type aliasis can be matched by adding a pattern-matching branch in function expr_of_type typ:

| {ptyp_desc = Ptyp_constr ({ txt = lid; _}, lst); _} -> 

Here, lid would be the name of the constructor, and lst is the list of “parameter” (honestly I don’t know the term, since the documentation didn’t explain this). Basically, if we have int list, lid would be "list", and lst would be a list containing a core_type of int. In the case of type i_list_list = i_list list, lst will be a list containing a core_type of i_list.

However, I cannot get the definition (int list) of i_list from the core_type of it, as i_list cannot be matched to patterns like [%type: [%t? t] list] , and I therefore cannot recursively find the base definition and implement the stringify function for types with type alias.

To get the definition, one can try to get the corresponding type_declaration from the core_type of the type alias, then get the field ptype_manifest. Notice that this can be done recursively, so it will be fine even if the definition contains type aliases.

I wonder if there are any ways to do so. Since ppxes like ppx_deriving.show have similar functionalities, I checked the source code, but wasn’t able to fully understand it. Here might be a related section, hopefully it helps: ppx_deriving/src_plugins/show/ppx_deriving_show.ml at 1268719e7117a80bcfe89c91a2c624a3eb171c8d · ocaml-ppx/ppx_deriving · GitHub

I have also found that the documentation of ppxlib is not that complete and does not include a clear explanation for each APIs. Are there any good resources?

Hi @ttzytt,

Apologies for any confusion from the tutorial, I wrote it 4 years ago and didn’t know a lot of OCaml then. The code in the tutorial is not necessarily the best. I would recommend the more official ppxlib documentation (which includes a small tutorial on building derivers). If you think things are missing (there are definitely a lot to add!) please do open an issue.

Now to the questions at hand. Most derivers have some naming scheme for the functions they are generating. When we encounter a type that is aliasing another type, we want to generate a function call to a presumably already generated function for that type. In the running example you are using this would be i_list_stringify. Now the code from the tutorial is a little outdated, and we can use Expansion_helpers to help. Here is a new case we can add to the expr_of_type function:

  | { ptyp_desc = Ptyp_constr (lid, args); _ } ->
    (* We generate the name with "_stringify" on the end *)
    let new_name = Expansion_helpers.mangle_lid (Suffix "stringify") lid.txt in
    let new_lid = { lid with txt = new_name } in
    (* We turn it into an identifier hoping we have already generated 
       the function either by hand or by using the ppx *)
    let fn = Exp.ident new_lid in
    (* We construct an application of this function to an argument.
       Note that we assume the function may be higher-order if the type
       contains parameters e.g. int list *)
    let app =
      if args = [] then fn else
      Exp.apply fn (List.map (fun x -> Nolabel, expr_of_type x) args) 
    in
    [%expr fun x -> [%e app] x]

Hopefully the documentation I linked to at the top can help a little. Please do open issues and I’ll be happy to help improve the documentation further. Hope this helps :))

1 Like

@patricoferris Thank you so much for the response with this example!

I can get the most part of this answer, but I was a bit unclear about the last part, where you construct an application of the function to an argument.

In my understanding, (List.map (fun x -> Nolabel, expr_of_type x) args) is used to generate a list of arguments for i_list_stringify. And Exp.apply generates an expression of that function application.

According to the documentation, Exp.apply is defined as:

Basically, an argument is a tuple of labels and expressions. For the expression part, you used expr_of_type x. But I thought that this is a function that takes in a core_type to output the expression of its stringify function. For example, the input of core_type of int will result in the output of the expression of string_of_int.

And we’re trying to construct the argument that is accepted by the function epxr_of_type, which should have a type of core_type, not (int -> expression). The error message after I run the example also shows this:

File "temp/ppx_stringify.ml", line 60, characters 19-69:
60 |       Exp.apply fn (List.map (fun x -> Nolabel, expr_of_type x) args) 
                        ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: This expression has type (arg_label * (int -> expression)) list
       but an expression was expected of type (arg_label * expression) list
       Type int -> expression is not compatible with type expression

So, I was thinking about passing in an expression of core_type, and came up with this:

Exp.apply fn (List.map (fun x -> Nolabel, [%expr x]) args) 

However, this resulted in the following error message:

60 |       Exp.apply fn (List.map (fun x -> Nolabel, [%expr x]) args) 
                                       ^
Error (warning 27 [unused-var-strict]): unused variable x.

Why is the variable x unused? I thought the purpose of [%expr] metaquot is to transform some OCaml code into the corresponding ast.

Regarding documentation. I think the official documentation of ppxlib you linked does a good job listing all the APIs, but more explanation would be really helpful.

For example, the documentation for Ast_helper.Exp is like this:

It states the types of arguments a function is accepting and the output type. However, it did not explain the purpose of this module: to convert something into expressions in the AST. Also, examples of using the APIs are not provided. For instance, some code snippets from what you posted

  | { ptyp_desc = Ptyp_constr (lid, args); _ } ->
    (* We generate the name with "_stringify" on the end *)
    let new_name = Expansion_helpers.mangle_lid (Suffix "stringify") lid.txt in
    let new_lid = { lid with txt = new_name } in
    (* We turn it into an identifier hoping we have already generated 
       the function either by hand or by using the ppx *)
    let fn = Exp.ident new_lid in
...

would be really helpful for beginners to understand the usage of Exp.Ident.

If you think the issues I pointed out are valid, I can open up an issue page later. But it seems to me that there is a lot of work to do for ppxlib’s documentation.

I’d also be happy to provide explanations and examples after I learn more about how to use it, as ppx is really a powerful and cool feature provided by the language.

1 Like

Yep, in this instance there is no label for any of the arguments and we just need to turn the core_type into an expression (i.e. the corresponding stringify function for that particular type). x is a core_type, it is one of the args from the Ptyp_constr. I’m not really sure why you are getting an error expecting another argument that is an integer, did you modify the code in any other way (e.g. new arguments to expr_of_type?). Here is the code that works locally for me: ppx_stringify.ml · GitHub

You are right but that x in [%expr x] is now just a new identifier and doesn’t actually reference the outer x. You need to antiquote it if you wanted to do that [%expr [%e x]].

1 Like

Sorry, I forgot to state that I added another argument representing the depth of the recursive call for expr_of_type for debugging. After some modifications, I found that your original answer is indeed correct.

What I still don’t quite get is why we are using the stringify function for a particular type as the expression of a core_type. Because that expression is a function at the end, what we wanted in expr_of_type is a type. Perhaps I didn’t completely get the full meaning of Exp.apply?

My previous question is the reason why I was thinking about using [%expr x] to transform the core_type into an expression (instead of using the stringify function). And I tried your modification of using [%expr [%e x]], it seems like the expression is transformed back to a core_type and thus incompatible with the argument accepted by Exp.apply:

File "temp/ppx_stringify.ml", line 33, characters 64-68:
33 |       Exp.apply fn (List.map (fun x -> Nolabel, [%expr [%e x]]) args) 
                                                                     ^^^^
Error: This expression has type core_type list
       but an expression was expected of type expression list
       Type core_type is not compatible with type expression

Thank you very much for all your responses. I know that, as a beginner, I might not express my question clearly. Please reply if you’d like some extra clarifications.

Just to hopefully help clear things up, here are a few points.

expr_of_type takes a core_type and derives an expression. That expression is the necessary function to convert core_type into a string. In the simplest case it will be a function core_type -> string. As you rightly pointed out in the case of int we get string_of_int

Some types are more complicated than just a primitive like int and they take “arguments”. We already saw one with int list. The ppx treats lists specially and captures them, but what if we tried a different type constructor that takes an argument?

type int_option = int option [@@deriving stringify] 
(* Unbound value option_stringify *)

We get this because of the new case we added to handle type constructors, but what type should option_stringify have? It needs to be able to handle any type we might give it. To allow this option_stringify must be a higher-order function:

let option_stringify convert = function
  | Some value -> "Some " ^ convert value
  | None -> "None"

With convert we could pass in a function for converting different values inside the option. For ints we could use string_of_int, for floats we could us string_of_float etc. Altogether our code now looks like:

let option_stringify convert = function
  | Some value -> "Some " ^ convert value
  | None -> "None"

type int_option = int option [@@deriving stringify] 

let () =
  let v = Some 10 in 
  print_endline (int_option_stringify v)

And if we look at what our ppx generated and specifically where the eapply was used (using dune describe pp example.ml):

let int_option_stringify x = 
  (* here is our eapply part:
      - option_stringify is the result of Exp.ident part
      - string_of_int is the result of recursively calling `expr_of_type` on the arguments 
        to this type (in this case there is only one, namely, `int`) *) 
  (option_stringify string_of_int) x

Hopefully that helps a little more. Also in terms of documentation, I couldn’t agree more. I’ll look into this shortly (I help maintain ppxlib) but please do open issues or continue to comment on the large documentation tracking issue. More examples using Ast_builder etc. would be great.

1 Like

Wow. Thank you so much! This explanation really helped me out, and I completely understand the approach now.

Can you point me to the specific issue page? So that I can comment on it.

Also, I do believe that the stringify deriver we just talked about would be a good example to add to here: examples (ppxlib.examples) (ocaml-ppx.github.io). As it showcases the core approach of ppx_deriving.show, a widely used ppx extension.

Perhaps I can try to work on it?

Hi @patricoferris,

I’ve made my comment on a documentation issue for ppxlib here: Improve documentation · Issue #324 · ocaml-ppx/ppxlib · GitHub. I’m not sure if this is the large documentation tracking issue you’re talking about.

By the way, I’ve noticed that your original ppxlib tutorial was posted on the Explore OCaml website. Seeing the about page’s emphasis on beginners and productivity workflow, I’d say that the website is definitely going to be helpful, as what I learned from your ppx tutorial. However, I checked the github page of this project. It seems like the development stopped 4 years ago. Is it no longer maintained, or is it just because there aren’t many people contributing content to it? I felt like this was a really cool project. Hopefully, after I learn more about ppxlib, I can contribute something to it. Anyway, thanks a lot for making the website.

I was mostly learning ppxlib by trying to add more functionalities to the stringify derived in your tutorial. One thing I was confused about is to support types with type variables like this:

type 'a my_option = 
  | None_ 
  | Some_ of 'a
type int_my_opt = int my_option

Using the pattern matching branch of | { ptyp_desc = Ptyp_constr (lid, args); _ }, we’re able to generate a correct stringify function for int_my_opt. This, as you mentioned previously, is dependent on the stringify function for my_option.

I first tried to search for the parts where ppx_deriving.show processes this scenario, but I wasn’t able to find an answer. Specifically, I used ppx_tool/dumpast to print out the AST of my_option:

==>
[{pstr_desc =
   Pstr_type (Recursive,
    [{ptype_name = {txt = "my_option"};
      ptype_params =
       [({ptyp_desc = Ptyp_var "a"; ptyp_loc_stack = []},
         (NoVariance, NoInjectivity))];
      ptype_cstrs = [];
      ptype_kind =
       Ptype_variant
        [{pcd_name = {txt = "None_"}; pcd_vars = [];
          pcd_args = Pcstr_tuple []; pcd_res = None};
         {pcd_name = {txt = "Some_"}; pcd_vars = [];
          pcd_args =
           Pcstr_tuple [{ptyp_desc = Ptyp_var "a"; ptyp_loc_stack = []}];
          pcd_res = None}];
      ptype_private = Public; ptype_manifest = None}])};
 {pstr_desc =
   Pstr_type (Recursive,
    [{ptype_name = {txt = "int_my_opt"}; ptype_params = []; ptype_cstrs = [];
      ptype_kind = Ptype_abstract; ptype_private = Public;
      ptype_manifest =
       Some
        {ptyp_desc =
          Ptyp_constr ({txt = Lident "my_option"},
           [{ptyp_desc = Ptyp_constr ({txt = Lident "int"}, []);
             ptyp_loc_stack = []}]);
         ptyp_loc_stack = []}}])}]
=========

And it seems that type variables like a are represented by the Ptyp_var constructor in the variant core_type_desc. I then searched Ptyp_var in ppx_deriving.show, it seems like it is used only in one line:

| { ptyp_desc = Ptyp_var name } -> [%expr [%e evar ("poly_"^name)] fmt]

Also, the library does not use ptype_params. So, I’m wondering if you have any ideas on how the feature of supporting type variables is being implemented.

I’ve noticed that ppx_deriving does not have too many comments and documentation, plus it is a pretty large library, so I guess it’s not the best place for beginners to learn about ppx. Do you have any recommendations on projects suitable for learning ppxlib?