Skip to content

Commit 1ce68db

Browse files
authored
flambda-backend: Modular syntax for types (#1401)
* [minor] Rename local variable * [minor] Formatting * Add support for Jane-syntax in types and in constructor arguments * Add empty `Core_type` and `Constructor_argument` Jane ASTs * Add matches on `Jane_syntax.Core_type.of_ast` * Respond to Richard's small comments * Add comment warning about an unavoidably missing Jane-syntax match * [minor] Double comma
1 parent 9f55ade commit 1ce68db

13 files changed

+171
-15
lines changed

parsing/ast_helper.ml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,12 @@ module Typ = struct
8585
let var_names = List.map (fun v -> v.txt) var_names in
8686
let rec loop t =
8787
let desc =
88+
(* This *ought* to match on [Jane_syntax.Core_type.ast_of] first, but
89+
that would be a dependency cycle -- [Jane_syntax] depends rather
90+
crucially on [Ast_helper]. However, this just recurses looking for
91+
constructors and variables, so it *should* be fine even so. If
92+
Jane-syntax embeddings ever change so that this breaks, we'll need to
93+
resolve this knot. *)
8894
match t.ptyp_desc with
8995
| Ptyp_any -> Ptyp_any
9096
| Ptyp_var x ->

parsing/ast_iterator.ml

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,7 @@ type iterator = {
6767
structure_item: iterator -> structure_item -> unit;
6868
structure_item_jane_syntax: iterator -> Jane_syntax.Structure_item.t -> unit;
6969
typ: iterator -> core_type -> unit;
70+
typ_jane_syntax: iterator -> Jane_syntax.Core_type.t -> unit;
7071
row_field: iterator -> row_field -> unit;
7172
object_field: iterator -> object_field -> unit;
7273
type_declaration: iterator -> type_declaration -> unit;
@@ -115,9 +116,16 @@ module T = struct
115116
| Otag (_, t) -> sub.typ sub t
116117
| Oinherit t -> sub.typ sub t
117118

118-
let iter sub {ptyp_desc = desc; ptyp_loc = loc; ptyp_attributes = attrs} =
119+
let iter_jst _sub : Jane_syntax.Core_type.t -> _ = function
120+
| _ -> .
121+
122+
let iter sub ({ptyp_desc = desc; ptyp_loc = loc; ptyp_attributes = attrs}
123+
as typ) =
119124
sub.location sub loc;
120125
sub.attributes sub attrs;
126+
match Jane_syntax.Core_type.of_ast typ with
127+
| Some jtyp -> sub.typ_jane_syntax sub jtyp
128+
| None ->
121129
match desc with
122130
| Ptyp_any
123131
| Ptyp_var _ -> ()
@@ -645,6 +653,7 @@ let default_iterator =
645653
type_declaration = T.iter_type_declaration;
646654
type_kind = T.iter_type_kind;
647655
typ = T.iter;
656+
typ_jane_syntax = T.iter_jst;
648657
row_field = T.row_field;
649658
object_field = T.object_field;
650659
type_extension = T.iter_type_extension;

parsing/ast_iterator.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,7 @@ type iterator = {
7070
structure_item: iterator -> structure_item -> unit;
7171
structure_item_jane_syntax: iterator -> Jane_syntax.Structure_item.t -> unit;
7272
typ: iterator -> core_type -> unit;
73+
typ_jane_syntax: iterator -> Jane_syntax.Core_type.t -> unit;
7374
row_field: iterator -> row_field -> unit;
7475
object_field: iterator -> object_field -> unit;
7576
type_declaration: iterator -> type_declaration -> unit;

parsing/ast_mapper.ml

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,7 @@ type mapper = {
7878
structure_item_jane_syntax: mapper ->
7979
Jane_syntax.Structure_item.t -> Jane_syntax.Structure_item.t;
8080
typ: mapper -> core_type -> core_type;
81+
typ_jane_syntax: mapper -> Jane_syntax.Core_type.t -> Jane_syntax.Core_type.t;
8182
type_declaration: mapper -> type_declaration -> type_declaration;
8283
type_extension: mapper -> type_extension -> type_extension;
8384
type_exception: mapper -> type_exception -> type_exception;
@@ -137,10 +138,22 @@ module T = struct
137138
in
138139
Of.mk ~loc ~attrs desc
139140

140-
let map sub {ptyp_desc = desc; ptyp_loc = loc; ptyp_attributes = attrs} =
141+
let map_jst _sub : Jane_syntax.Core_type.t -> Jane_syntax.Core_type.t =
142+
function
143+
| _ -> .
144+
145+
let map sub ({ptyp_desc = desc; ptyp_loc = loc; ptyp_attributes = attrs}
146+
as typ) =
141147
let open Typ in
142148
let loc = sub.location sub loc in
143149
let attrs = sub.attributes sub attrs in
150+
match Jane_syntax.Core_type.of_ast typ with
151+
| Some jtyp -> begin
152+
Jane_syntax_parsing.Core_type.wrap_desc ~loc ~attrs @@
153+
match sub.typ_jane_syntax sub jtyp with
154+
| _ -> .
155+
end
156+
| None ->
144157
match desc with
145158
| Ptyp_any -> any ~loc ~attrs ()
146159
| Ptyp_var s -> var ~loc ~attrs s
@@ -740,6 +753,7 @@ let default_mapper =
740753
type_declaration = T.map_type_declaration;
741754
type_kind = T.map_type_kind;
742755
typ = T.map;
756+
typ_jane_syntax = T.map_jst;
743757
type_extension = T.map_type_extension;
744758
type_exception = T.map_type_exception;
745759
extension_constructor = T.map_extension_constructor;

parsing/ast_mapper.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -116,6 +116,7 @@ type mapper = {
116116
structure_item_jane_syntax: mapper ->
117117
Jane_syntax.Structure_item.t -> Jane_syntax.Structure_item.t;
118118
typ: mapper -> core_type -> core_type;
119+
typ_jane_syntax: mapper -> Jane_syntax.Core_type.t -> Jane_syntax.Core_type.t;
119120
type_declaration: mapper -> type_declaration -> type_declaration;
120121
type_extension: mapper -> type_extension -> type_extension;
121122
type_exception: mapper -> type_exception -> type_exception;

parsing/depend.ml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -96,6 +96,9 @@ let handle_extension ext =
9696
()
9797

9898
let rec add_type bv ty =
99+
match Jane_syntax.Core_type.of_ast ty with
100+
| Some jty -> add_type_jst bv jty
101+
| None ->
99102
match ty.ptyp_desc with
100103
Ptyp_any -> ()
101104
| Ptyp_var _ -> ()
@@ -119,6 +122,9 @@ let rec add_type bv ty =
119122
| Ptyp_package pt -> add_package_type bv pt
120123
| Ptyp_extension e -> handle_extension e
121124

125+
and add_type_jst _bv : Jane_syntax.Core_type.t -> _ = function
126+
| _ -> .
127+
122128
and add_package_type bv (lid, l) =
123129
add bv lid;
124130
List.iter (add_type bv) (List.map (fun (_, e) -> e) l)

parsing/jane_syntax.ml

Lines changed: 29 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -278,7 +278,7 @@ module Immutable_arrays = struct
278278
Pattern.make_entire_jane_syntax ~loc extension_string (fun () ->
279279
Ast_helper.Pat.array elts)
280280

281-
let of_pat expr = match expr.ppat_desc with
281+
let of_pat pat = match pat.ppat_desc with
282282
| Ppat_array elts -> Iapat_immutable_array elts
283283
| _ -> failwith "Malformed immutable array pattern"
284284
end
@@ -347,6 +347,34 @@ module type AST = sig
347347
val of_ast : ast -> t option
348348
end
349349

350+
module Core_type = struct
351+
module M = struct
352+
module AST = Jane_syntax_parsing.Core_type
353+
354+
type t = |
355+
356+
let of_ast_internal (feat : Feature.t) _typ = match feat with
357+
| _ -> None
358+
end
359+
360+
include M
361+
include Make_of_ast(M)
362+
end
363+
364+
module Constructor_argument = struct
365+
module M = struct
366+
module AST = Jane_syntax_parsing.Constructor_argument
367+
368+
type t = |
369+
370+
let of_ast_internal (feat : Feature.t) _carg = match feat with
371+
| _ -> None
372+
end
373+
374+
include M
375+
include Make_of_ast(M)
376+
end
377+
350378
module Expression = struct
351379
module M = struct
352380
module AST = Jane_syntax_parsing.Expression

parsing/jane_syntax.mli

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -173,6 +173,21 @@ end
173173
(******************************************)
174174
(* Individual syntactic categories *)
175175

176+
(** Novel syntax in types *)
177+
module Core_type : sig
178+
type t = |
179+
180+
include AST with type t := t and type ast := Parsetree.core_type
181+
end
182+
183+
(** Novel syntax in constructor arguments; this isn't a core AST type,
184+
but captures where [global_] and [nonlocal_] live *)
185+
module Constructor_argument : sig
186+
type t = |
187+
188+
include AST with type t := t and type ast := Parsetree.core_type
189+
end
190+
176191
(** Novel syntax in expressions *)
177192
module Expression : sig
178193
type t =

parsing/jane_syntax_parsing.ml

Lines changed: 40 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -415,6 +415,45 @@ module Make_AST (AST_parameters : AST_parameters) :
415415
| None -> None
416416
end
417417

418+
(** The AST parameters for every subset of types; embedded as
419+
[[[%jane.FEATNAME] * BODY]]. *)
420+
module Type_AST_parameters = struct
421+
type ast = core_type
422+
type ast_desc = core_type_desc
423+
424+
(* Missing [plural] *)
425+
426+
let location typ = typ.ptyp_loc
427+
428+
let wrap_desc ?loc ~attrs = Ast_helper.Typ.mk ?loc ~attrs
429+
430+
let make_extension_node = Ast_helper.Typ.extension
431+
432+
let make_extension_use ~extension_node typ =
433+
Ptyp_tuple [extension_node; typ]
434+
435+
let match_extension_use typ =
436+
match typ.ptyp_desc with
437+
| Ptyp_tuple([{ptyp_desc = Ptyp_extension ext; _}; typ]) ->
438+
Some (ext, typ)
439+
| _ ->
440+
None
441+
end
442+
443+
(** Types; embedded as [[[%jane.FEATNAME] * BODY]]. *)
444+
module Core_type = Make_AST(struct
445+
include Type_AST_parameters
446+
447+
let plural = "types"
448+
end)
449+
450+
(** Constructor arguments; the same as types, but used in fewer places *)
451+
module Constructor_argument = Make_AST(struct
452+
include Type_AST_parameters
453+
454+
let plural = "constructor arguments"
455+
end)
456+
418457
(** Expressions; embedded as [([%jane.FEATNAME] BODY)]. *)
419458
module Expression = Make_AST(struct
420459
type ast = expression
@@ -461,7 +500,7 @@ module Pattern = Make_AST(struct
461500
| Ppat_tuple([{ppat_desc = Ppat_extension ext; _}; pattern]) ->
462501
Some (ext, pattern)
463502
| _ ->
464-
None
503+
None
465504
end)
466505

467506
(** Module types; embedded as [functor (_ : [%jane.FEATNAME]) -> BODY]. *)

parsing/jane_syntax_parsing.mli

Lines changed: 27 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -169,16 +169,33 @@ end
169169
adding these lazily as we need them. When you add another one, make
170170
sure also to add special handling in [Ast_iterator] and [Ast_mapper]. *)
171171

172-
module Expression : AST with type ast = Parsetree.expression
173-
and type ast_desc = Parsetree.expression_desc
174-
module Pattern : AST with type ast = Parsetree.pattern
175-
and type ast_desc = Parsetree.pattern_desc
176-
module Module_type : AST with type ast = Parsetree.module_type
177-
and type ast_desc = Parsetree.module_type_desc
178-
module Signature_item : AST with type ast = Parsetree.signature_item
179-
and type ast_desc = Parsetree.signature_item_desc
180-
module Structure_item : AST with type ast = Parsetree.structure_item
181-
and type ast_desc = Parsetree.structure_item_desc
172+
module Core_type : AST
173+
with type ast = Parsetree.core_type
174+
and type ast_desc = Parsetree.core_type_desc
175+
176+
module Constructor_argument : AST
177+
with type ast = Parsetree.core_type
178+
and type ast_desc = Parsetree.core_type_desc
179+
180+
module Expression : AST
181+
with type ast = Parsetree.expression
182+
and type ast_desc = Parsetree.expression_desc
183+
184+
module Pattern : AST
185+
with type ast = Parsetree.pattern
186+
and type ast_desc = Parsetree.pattern_desc
187+
188+
module Module_type : AST
189+
with type ast = Parsetree.module_type
190+
and type ast_desc = Parsetree.module_type_desc
191+
192+
module Signature_item : AST
193+
with type ast = Parsetree.signature_item
194+
and type ast_desc = Parsetree.signature_item_desc
195+
196+
module Structure_item : AST
197+
with type ast = Parsetree.structure_item
198+
and type ast_desc = Parsetree.structure_item_desc
182199

183200
(** Each syntactic category will include a module that meets this signature.
184201
Then, the [Make_of_ast] functor produces the functions that actually convert

parsing/pprintast.ml

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -344,7 +344,11 @@ and core_type ctxt f x =
344344

345345
and core_type1 ctxt f x =
346346
if has_non_curry_attr x.ptyp_attributes then core_type ctxt f x
347-
else match x.ptyp_desc with
347+
else
348+
match Jane_syntax.Core_type.of_ast x with
349+
| Some jtyp -> core_type1_jane_syntax ctxt f jtyp
350+
| None ->
351+
match x.ptyp_desc with
348352
| Ptyp_any -> pp f "_";
349353
| Ptyp_var s -> tyvar f s;
350354
| Ptyp_tuple l -> pp f "(%a)" (list (core_type1 ctxt) ~sep:"@;*@;") l
@@ -420,6 +424,9 @@ and core_type1 ctxt f x =
420424
| Ptyp_extension e -> extension ctxt f e
421425
| _ -> paren true (core_type ctxt) f x
422426

427+
and core_type1_jane_syntax _ctxt _f : Jane_syntax.Core_type.t -> _ = function
428+
| _ -> .
429+
423430
and return_type ctxt f x =
424431
if x.ptyp_attributes <> [] then maybe_local_type core_type1 ctxt f x
425432
else maybe_local_type core_type ctxt f x

typing/typecore.ml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3460,6 +3460,9 @@ let is_local_returning_function cases =
34603460
(* Approximate the type of an expression, for better recursion *)
34613461

34623462
let rec approx_type env sty =
3463+
match Jane_syntax.Core_type.of_ast sty with
3464+
| Some jty -> approx_type_jst env jty
3465+
| None ->
34633466
match sty.ptyp_desc with
34643467
| Ptyp_arrow (p, ({ ptyp_desc = Ptyp_poly _ } as arg_sty), sty) ->
34653468
(* CR layouts v5: value requirement here to be relaxed *)
@@ -3502,6 +3505,9 @@ let rec approx_type env sty =
35023505
(which mentions approx_type) for why it can't be value. *)
35033506
| _ -> newvar Layout.any
35043507

3508+
and approx_type_jst _env : Jane_syntax.Core_type.t -> _ = function
3509+
| _ -> .
3510+
35053511
let type_pattern_approx_jane_syntax : Jane_syntax.Pattern.t -> _ = function
35063512
| Jpat_immutable_array _ -> ()
35073513

typing/typetexp.ml

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -431,6 +431,9 @@ and transl_type_aux env policy mode styp =
431431
{ ctyp_desc; ctyp_type; ctyp_env = env;
432432
ctyp_loc = loc; ctyp_attributes = styp.ptyp_attributes }
433433
in
434+
match Jane_syntax.Core_type.of_ast styp with
435+
| Some etyp -> transl_type_aux_jst env policy mode etyp
436+
| None ->
434437
match styp.ptyp_desc with
435438
Ptyp_any ->
436439
let ty = TyVarEnv.new_anon_var styp.ptyp_loc env Layout.any policy in
@@ -822,6 +825,10 @@ and transl_type_aux env policy mode styp =
822825
| Ptyp_extension ext ->
823826
raise (Error_forward (Builtin_attributes.error_of_extension ext))
824827

828+
and transl_type_aux_jst _env _policy _mode
829+
: Jane_syntax.Core_type.t -> _ = function
830+
| _ -> .
831+
825832
and transl_fields env policy o fields =
826833
let hfields = Hashtbl.create 17 in
827834
let add_typed_field loc l ty =

0 commit comments

Comments
 (0)