Skip to content

Commit 87e8143

Browse files
authored
Syntactic support for instance names as identifiers (#1873)
1 parent 7f34929 commit 87e8143

29 files changed

+445
-101
lines changed

ocaml/driver/compile_common.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ let emit_signature info alerts tsg =
9090
else begin
9191
let cmi_arg_for =
9292
match !Clflags.as_argument_for with
93-
| Some arg_type -> Some (Global_module.Name.create arg_type [])
93+
| Some arg_type -> Some (Global_module.Name.create_no_args arg_type)
9494
| None -> None
9595
in
9696
Normal { cmi_impl = info.module_name; cmi_arg_for }

ocaml/parsing/ast_iterator.ml

+21-1
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ type iterator = {
5656
module_declaration: iterator -> module_declaration -> unit;
5757
module_substitution: iterator -> module_substitution -> unit;
5858
module_expr: iterator -> module_expr -> unit;
59+
module_expr_jane_syntax: iterator -> Jane_syntax.Module_expr.t -> unit;
5960
module_type: iterator -> module_type -> unit;
6061
module_type_declaration: iterator -> module_type_declaration -> unit;
6162
module_type_jane_syntax: iterator -> Jane_syntax.Module_type.t -> unit;
@@ -403,9 +404,27 @@ end
403404
module M = struct
404405
(* Value expressions for the module language *)
405406

406-
let iter sub {pmod_loc = loc; pmod_desc = desc; pmod_attributes = attrs} =
407+
module I = Jane_syntax.Instances
408+
409+
let iter_instance _sub : I.instance -> _ = function
410+
| _ ->
411+
(* CR lmaurer: Implement this. Might want to change the [instance] type to have
412+
Ids with locations in them rather than just raw strings. *)
413+
()
414+
415+
let iter_instance_expr sub : I.module_expr -> _ = function
416+
| Imod_instance i -> iter_instance sub i
417+
418+
let iter_ext sub : Jane_syntax.Module_expr.t -> _ = function
419+
| Emod_instance i -> iter_instance_expr sub i
420+
421+
let iter sub
422+
({pmod_loc = loc; pmod_desc = desc; pmod_attributes = attrs} as expr) =
407423
sub.location sub loc;
408424
sub.attributes sub attrs;
425+
match Jane_syntax.Module_expr.of_ast expr with
426+
| Some ext -> sub.module_expr_jane_syntax sub ext
427+
| None ->
409428
match desc with
410429
| Pmod_ident x -> iter_loc sub x
411430
| Pmod_structure str -> sub.structure sub str
@@ -760,6 +779,7 @@ let default_iterator =
760779
structure_item = M.iter_structure_item;
761780
structure_item_jane_syntax = M.iter_structure_item_jst;
762781
module_expr = M.iter;
782+
module_expr_jane_syntax = M.iter_ext;
763783
signature = (fun this l -> List.iter (this.signature_item this) l);
764784
signature_item = MT.iter_signature_item;
765785
signature_item_jane_syntax = MT.iter_signature_item_jst;

ocaml/parsing/ast_iterator.mli

+1
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@ type iterator = {
5959
module_declaration: iterator -> module_declaration -> unit;
6060
module_substitution: iterator -> module_substitution -> unit;
6161
module_expr: iterator -> module_expr -> unit;
62+
module_expr_jane_syntax: iterator -> Jane_syntax.Module_expr.t -> unit;
6263
module_type: iterator -> module_type -> unit;
6364
module_type_declaration: iterator -> module_type_declaration -> unit;
6465
module_type_jane_syntax: iterator -> Jane_syntax.Module_type.t -> unit;

ocaml/parsing/ast_mapper.ml

+25-1
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,8 @@ type mapper = {
9494
Jane_syntax.Extension_constructor.t -> Jane_syntax.Extension_constructor.t;
9595
module_type_jane_syntax: mapper
9696
-> Jane_syntax.Module_type.t -> Jane_syntax.Module_type.t;
97+
module_expr_jane_syntax: mapper
98+
-> Jane_syntax.Module_expr.t -> Jane_syntax.Module_expr.t;
9799
pat_jane_syntax: mapper -> Jane_syntax.Pattern.t -> Jane_syntax.Pattern.t;
98100
signature_item_jane_syntax: mapper ->
99101
Jane_syntax.Signature_item.t -> Jane_syntax.Signature_item.t;
@@ -479,12 +481,33 @@ end
479481

480482

481483
module M = struct
484+
module I = Jane_syntax.Instances
485+
482486
(* Value expressions for the module language *)
487+
let map_instance _sub : I.instance -> I.instance = function
488+
| i ->
489+
(* CR lmaurer: Implement this. Might want to change the [instance] type to have
490+
Ids with locations in them rather than just raw strings. *)
491+
i
492+
493+
let map_instance_expr sub : I.module_expr -> I.module_expr = function
494+
| Imod_instance i -> Imod_instance (map_instance sub i)
495+
496+
let map_ext sub : Jane_syntax.Module_expr.t -> Jane_syntax.Module_expr.t =
497+
function
498+
| Emod_instance i -> Emod_instance (map_instance_expr sub i)
483499

484-
let map sub {pmod_loc = loc; pmod_desc = desc; pmod_attributes = attrs} =
500+
let map sub
501+
({pmod_loc = loc; pmod_desc = desc; pmod_attributes = attrs} as mexpr) =
485502
let open Mod in
486503
let loc = sub.location sub loc in
487504
let attrs = sub.attributes sub attrs in
505+
match Jane_syntax.Module_expr.of_ast mexpr with
506+
| Some ext -> begin
507+
match sub.module_expr_jane_syntax sub ext with
508+
| Emod_instance i -> Jane_syntax.Instances.module_expr_of ~loc i
509+
end
510+
| None ->
488511
match desc with
489512
| Pmod_ident x -> ident ~loc ~attrs (map_loc sub x)
490513
| Pmod_structure str -> structure ~loc ~attrs (sub.structure sub str)
@@ -887,6 +910,7 @@ let default_mapper =
887910
structure = (fun this l -> List.map (this.structure_item this) l);
888911
structure_item = M.map_structure_item;
889912
module_expr = M.map;
913+
module_expr_jane_syntax = M.map_ext;
890914
signature = (fun this l -> List.map (this.signature_item this) l);
891915
signature_item = MT.map_signature_item;
892916
module_type = MT.map;

ocaml/parsing/ast_mapper.mli

+2
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,8 @@ type mapper = {
129129
Jane_syntax.Extension_constructor.t -> Jane_syntax.Extension_constructor.t;
130130
module_type_jane_syntax: mapper ->
131131
Jane_syntax.Module_type.t -> Jane_syntax.Module_type.t;
132+
module_expr_jane_syntax: mapper ->
133+
Jane_syntax.Module_expr.t -> Jane_syntax.Module_expr.t;
132134
pat_jane_syntax: mapper -> Jane_syntax.Pattern.t -> Jane_syntax.Pattern.t;
133135
signature_item_jane_syntax: mapper ->
134136
Jane_syntax.Signature_item.t -> Jane_syntax.Signature_item.t;

ocaml/parsing/jane_syntax.ml

+80
Original file line numberDiff line numberDiff line change
@@ -1261,6 +1261,74 @@ module Layouts = struct
12611261
| _ -> failwith "Malformed [kind_abbrev] in structure"
12621262
end
12631263

1264+
module Instances = struct
1265+
type instance =
1266+
{ head : string;
1267+
args : (string * instance) list
1268+
}
1269+
1270+
type module_expr = Imod_instance of instance
1271+
1272+
let feature : Feature.t = Language_extension Instances
1273+
1274+
let module_expr_of_string ~loc str =
1275+
Ast_helper.Mod.ident ~loc { txt = Lident str; loc }
1276+
1277+
let rec module_expr_of_instance ~loc { head; args } =
1278+
let head = module_expr_of_string ~loc head in
1279+
match args with
1280+
| [] -> head
1281+
| _ ->
1282+
let args =
1283+
List.concat_map
1284+
(fun (param, value) ->
1285+
let param = module_expr_of_string ~loc param in
1286+
let value = module_expr_of_instance ~loc value in
1287+
[param; value])
1288+
args
1289+
in
1290+
List.fold_left (Ast_helper.Mod.apply ~loc) head args
1291+
1292+
let module_expr_of ~loc = function
1293+
| Imod_instance instance ->
1294+
Module_expr.make_entire_jane_syntax ~loc feature (fun () ->
1295+
module_expr_of_instance ~loc instance)
1296+
1297+
let head_of_ident (lid : Longident.t Location.loc) =
1298+
match lid with
1299+
| { txt = Lident s; loc = _ } -> s
1300+
| _ -> failwith "Malformed instance identifier"
1301+
1302+
let gather_args mexpr =
1303+
let rec loop mexpr rev_acc =
1304+
match mexpr.pmod_desc with
1305+
| Pmod_apply (f, v) -> (
1306+
match f.pmod_desc with
1307+
| Pmod_apply (f, n) -> loop f ((n, v) :: rev_acc)
1308+
| _ -> failwith "Malformed instance identifier")
1309+
| head -> head, List.rev rev_acc
1310+
in
1311+
loop mexpr []
1312+
1313+
let string_of_module_expr mexpr =
1314+
match mexpr.pmod_desc with
1315+
| Pmod_ident i -> head_of_ident i
1316+
| _ -> failwith "Malformed instance identifier"
1317+
1318+
let rec instance_of_module_expr mexpr =
1319+
match gather_args mexpr with
1320+
| Pmod_ident i, args ->
1321+
let head = head_of_ident i in
1322+
let args = List.map instances_of_arg_pair args in
1323+
{ head; args }
1324+
| _ -> failwith "Malformed instance identifier"
1325+
1326+
and instances_of_arg_pair (n, v) =
1327+
string_of_module_expr n, instance_of_module_expr v
1328+
1329+
let of_module_expr mexpr = Imod_instance (instance_of_module_expr mexpr)
1330+
end
1331+
12641332
(******************************************************************************)
12651333
(** The interface to our novel syntax, which we export *)
12661334

@@ -1391,6 +1459,18 @@ module Module_type = struct
13911459
{ mty with pmty_attributes = mty.pmty_attributes @ attrs }
13921460
end
13931461

1462+
module Module_expr = struct
1463+
type t = Emod_instance of Instances.module_expr
1464+
1465+
let of_ast_internal (feat : Feature.t) sigi =
1466+
match feat with
1467+
| Language_extension Instances ->
1468+
Some (Emod_instance (Instances.of_module_expr sigi))
1469+
| _ -> None
1470+
1471+
let of_ast = Module_expr.make_of_ast ~of_ast_internal
1472+
end
1473+
13941474
module Signature_item = struct
13951475
type t = Jsig_layout of Layouts.signature_item
13961476

ocaml/parsing/jane_syntax.mli

+20
Original file line numberDiff line numberDiff line change
@@ -276,6 +276,19 @@ module Layouts : sig
276276
(Jkind.annotation * Parsetree.attributes) option
277277
end
278278

279+
module Instances : sig
280+
(** The name of an instance module. Gets converted to [Global.Name.t] in the
281+
flambda-backend compiler. *)
282+
type instance =
283+
{ head : string;
284+
args : (string * instance) list
285+
}
286+
287+
type module_expr = Imod_instance of instance
288+
289+
val module_expr_of : loc:Location.t -> module_expr -> Parsetree.module_expr
290+
end
291+
279292
(******************************************)
280293
(* General facility, which we export *)
281294

@@ -452,3 +465,10 @@ module Extension_constructor : sig
452465
t ->
453466
Parsetree.extension_constructor
454467
end
468+
469+
(** Novel syntax in module expressions *)
470+
module Module_expr : sig
471+
type t = Emod_instance of Instances.module_expr
472+
473+
include AST with type t := t and type ast := Parsetree.module_expr
474+
end

ocaml/parsing/jane_syntax_parsing.ml

+16
Original file line numberDiff line numberDiff line change
@@ -633,6 +633,21 @@ module Module_type0 = Make_with_attribute (struct
633633
let with_attributes mty pmty_attributes = { mty with pmty_attributes }
634634
end)
635635

636+
(** Module expressions; embedded using an attribute on the module expression. *)
637+
module Module_expr0 = Make_with_attribute (struct
638+
type ast = module_expr
639+
640+
let plural = "module expressions"
641+
642+
let location mexpr = mexpr.pmod_loc
643+
644+
let with_location mexpr l = { mexpr with pmod_loc = l }
645+
646+
let attributes mexpr = mexpr.pmod_attributes
647+
648+
let with_attributes mexpr pmod_attributes = { mexpr with pmod_attributes }
649+
end)
650+
636651
(** Extension constructors; embedded using an attribute. *)
637652
module Extension_constructor0 = Make_with_attribute (struct
638653
type ast = extension_constructor
@@ -849,6 +864,7 @@ let make_jane_syntax_attribute feature trailing_components payload =
849864
module Expression = Make_ast (Expression0)
850865
module Pattern = Make_ast (Pattern0)
851866
module Module_type = Make_ast (Module_type0)
867+
module Module_expr = Make_ast (Module_expr0)
852868
module Signature_item = Make_ast (Signature_item0)
853869
module Structure_item = Make_ast (Structure_item0)
854870
module Core_type = Make_ast (Core_type0)

ocaml/parsing/jane_syntax_parsing.mli

+2
Original file line numberDiff line numberDiff line change
@@ -202,6 +202,8 @@ module Pattern : AST with type ast = Parsetree.pattern
202202

203203
module Module_type : AST with type ast = Parsetree.module_type
204204

205+
module Module_expr : AST with type ast = Parsetree.module_expr
206+
205207
module Signature_item : AST with type ast = Parsetree.signature_item
206208

207209
module Structure_item : AST with type ast = Parsetree.structure_item

ocaml/parsing/pprintast.ml

+20-1
Original file line numberDiff line numberDiff line change
@@ -1643,7 +1643,9 @@ and module_expr ctxt f x =
16431643
if x.pmod_attributes <> [] then
16441644
pp f "((%a)%a)" (module_expr ctxt) {x with pmod_attributes=[]}
16451645
(attributes ctxt) x.pmod_attributes
1646-
else match x.pmod_desc with
1646+
else match Jane_syntax.Module_expr.of_ast x with
1647+
| Some ext -> extension_module_expr ctxt f ext
1648+
| None -> match x.pmod_desc with
16471649
| Pmod_structure (s) ->
16481650
pp f "@[<hv2>struct@;@[<0>%a@]@;<1 -2>end@]"
16491651
(list (structure_item ctxt) ~sep:"@\n") s;
@@ -2342,6 +2344,23 @@ and labeled_tuple_expr ctxt f ~unboxed x =
23422344
pp f "@[<hov2>%s(%a)@]" (if unboxed then "#" else "")
23432345
(list (tuple_component ctxt) ~sep:",@;") x
23442346

2347+
and extension_module_expr ctxt f (x : Jane_syntax.Module_expr.t) =
2348+
match x with
2349+
| Emod_instance i -> instance_module_expr ctxt f i
2350+
2351+
and instance_module_expr ctxt f (x : Jane_syntax.Instances.module_expr) =
2352+
match x with
2353+
| Imod_instance i -> instance ctxt f i
2354+
2355+
and instance ctxt f (x : Jane_syntax.Instances.instance) =
2356+
match x with
2357+
| { head; args = [] } -> pp f "%s" head
2358+
| { head; args } ->
2359+
pp f "@[<2>%s %a@]" head (list (instance_arg ctxt)) args
2360+
2361+
and instance_arg ctxt f (param, value) =
2362+
pp f "@[<1>(%s)@;(%a)@]" param (instance ctxt) value
2363+
23452364
(******************************************************************************)
23462365
(* All exported functions must be defined or redefined below here and wrapped in
23472366
[export_printer] in order to ensure they are invariant with respecto which

ocaml/testsuite/tests/language-extensions/pprintast_unconditional.ml

+6
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,11 @@ module Example = struct
8181
kind_abbrev_ data = value mod sync many \
8282
end"
8383

84+
let instance_name =
85+
parse module_expr "\
86+
Base(Name1)(Value1)(Name2)(Value2(Name2_1)(Value2_1)) \
87+
[@jane.non_erasable.instances]"
88+
8489
let longident = parse longident "No.Longidents.Require.extensions"
8590
let expression = parse expression "[x for x = 1 to 10]"
8691
let pattern = parse pattern "[:_:]"
@@ -231,6 +236,7 @@ end = struct
231236
let string_of_structure = test_string_of "string_of_structure" string_of_structure Example.structure
232237
let modal_kind_struct = test "modal_kind_struct" module_expr Example.modal_kind_struct
233238
let modal_kind_sig = test "modal_kind_sig" module_type Example.modal_kind_sig
239+
let instance_name = test "instance_name" module_expr Example.instance_name
234240

235241
let tyvar_of_name =
236242
test_string_of "tyvar_of_name" tyvar_of_name Example.tyvar_of_name

ocaml/testsuite/tests/language-extensions/pprintast_unconditional.reference

+8
Original file line numberDiff line numberDiff line change
@@ -122,6 +122,10 @@ modal_kind_sig:
122122
kind_abbrev_ data = value mod sync many
123123
end
124124

125+
instance_name:
126+
((((((Base)(Name1))(Value1))(Name2))(((Value2)(Name2_1))(Value2_1)))
127+
[@jane.non_erasable.instances ])
128+
125129
tyvar_of_name: 'no_tyvars_require_extensions
126130

127131
tyvar: 'no_tyvars_require_extensions
@@ -256,6 +260,10 @@ modal_kind_sig:
256260
kind_abbrev_ data = value mod sync many
257261
end
258262

263+
instance_name:
264+
((((((Base)(Name1))(Value1))(Name2))(((Value2)(Name2_1))(Value2_1)))
265+
[@jane.non_erasable.instances ])
266+
259267
tyvar_of_name: 'no_tyvars_require_extensions
260268

261269
tyvar: 'no_tyvars_require_extensions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
module Monoid_utils_of_list_monoid =
2+
Monoid_utils(Monoid)(List_monoid)(Monoid)(List_monoid) [@jane.non_erasable.instances]
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
File "bad_instance_repeated_arg_name.ml", line 2, characters 2-56:
2+
2 | Monoid_utils(Monoid)(List_monoid)(Monoid)(List_monoid) [@jane.non_erasable.instances]
3+
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
4+
Error: This instance has multiple arguments with the name "Monoid".

0 commit comments

Comments
 (0)