Source file bin_shape_expand.ml
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
open Base
open Ppxlib
open Ast_builder.Default
let raise_errorf ~loc fmt =
Location.raise_errorf ~loc (Stdlib.( ^^ ) "ppx_bin_shape: " fmt)
;;
let loc_string loc ~hide_loc =
let loc_expr =
if hide_loc
then [%expr "<hidden>"]
else Ppx_here_expander.lift_position_as_string ~loc
in
[%expr Bin_prot.Shape.Location.of_string [%e loc_expr]]
;;
let app_list ~loc (func : expression) (args : expression list) =
[%expr [%e func] [%e elist ~loc args]]
;;
let curry_app_list ~loc (func : expression) (args : expression list) =
List.fold_left args ~init:func ~f:(fun acc arg -> [%expr [%e acc] [%e arg]])
;;
let bin_shape_ tname = "bin_shape_" ^ tname
let bin_shape_lid ~loc id = unapplied_type_constr_conv ~loc id ~f:bin_shape_
let shape_tid ~loc ~(tname : string) =
[%expr Bin_prot.Shape.Tid.of_string [%e estring ~loc tname]]
;;
let shape_vid ~loc ~(tvar : string) =
[%expr Bin_prot.Shape.Vid.of_string [%e estring ~loc tvar]]
;;
let shape_rec_app ~loc ~(tname : string) =
[%expr Bin_prot.Shape.rec_app [%e shape_tid ~loc ~tname]]
;;
let shape_top_app ~loc ~(tname : string) =
[%expr Bin_prot.Shape.top_app _group [%e shape_tid ~loc ~tname]]
;;
let shape_tuple ~loc (exps : expression list) =
[%expr Bin_prot.Shape.tuple [%e elist ~loc exps]]
;;
let shape_record ~loc (xs : (string * expression) list) =
[%expr
Bin_prot.Shape.record
[%e elist ~loc (List.map xs ~f:(fun (s, e) -> [%expr [%e estring ~loc s], [%e e]]))]]
;;
let shape_variant ~loc (xs : (string * expression list) list) =
[%expr
Bin_prot.Shape.variant
[%e
elist
~loc
(List.map xs ~f:(fun (s, es) -> [%expr [%e estring ~loc s], [%e elist ~loc es]]))]]
;;
let shape_poly_variant ~loc ~hide_loc (xs : expression list) =
[%expr Bin_prot.Shape.poly_variant [%e loc_string loc ~hide_loc] [%e elist ~loc xs]]
;;
type string_literal_or_other_expression =
| String_literal of string
| Other_expression of expression
let string_literal f s = f (String_literal s)
let other_expression f e = f (Other_expression e)
let shape_annotate ~loc ~name (x : expression) =
let name =
match name with
| Other_expression e -> e
| String_literal s -> [%expr Bin_prot.Shape.Uuid.of_string [%e estring ~loc s]]
in
[%expr Bin_prot.Shape.annotate [%e name] [%e x]]
;;
let shape_basetype ~loc ~uuid (xs : expression list) =
let uuid =
match uuid with
| Other_expression e -> e
| String_literal s -> [%expr Bin_prot.Shape.Uuid.of_string [%e estring ~loc s]]
in
app_list ~loc [%expr Bin_prot.Shape.basetype [%e uuid]] xs
;;
module Context : sig
type t
val create : type_declaration list -> t
val is_local : t -> tname:string -> bool
end = struct
type t = { tds : type_declaration list }
let create tds = { tds }
let is_local t ~tname =
List.exists t.tds ~f:(fun td -> String.equal tname td.ptype_name.txt)
;;
end
let expr_error ~loc msg =
pexp_extension
~loc
(Location.Error.to_extension (Location.Error.createf ~loc "ppx_bin_shape: %s" msg))
;;
let expr_errorf ~loc = Printf.ksprintf (fun msg -> expr_error ~loc msg)
let of_type
: allow_free_vars:bool -> hide_loc:bool -> context:Context.t -> core_type -> expression
=
fun ~allow_free_vars ~hide_loc ~context ->
let rec traverse_row ~loc ~typ_for_error (row : row_field) : expression =
match row.prf_desc with
| Rtag (_, true, _ :: _) | Rtag (_, false, _ :: _ :: _) ->
expr_errorf
~loc
"unsupported '&' in row_field: %s"
(string_of_core_type typ_for_error)
| Rtag ({ txt; _ }, true, []) ->
[%expr Bin_prot.Shape.constr [%e estring ~loc txt] None]
| Rtag ({ txt; _ }, false, [ t ]) ->
[%expr Bin_prot.Shape.constr [%e estring ~loc txt] (Some [%e traverse t])]
| Rtag (_, false, []) -> expr_error ~loc "impossible row_type: Rtag (_,_,false,[])"
| Rinherit t ->
[%expr
Bin_prot.Shape.inherit_
[%e loc_string { t.ptyp_loc with loc_ghost = true } ~hide_loc]
[%e traverse t]]
and traverse typ =
let loc = { typ.ptyp_loc with loc_ghost = true } in
match typ.ptyp_desc with
| Ptyp_constr (lid, typs) ->
let args = List.map typs ~f:traverse in
(match
match lid.txt with
| Lident tname -> if Context.is_local context ~tname then Some tname else None
| _ -> None
with
| Some tname -> app_list ~loc (shape_rec_app ~loc ~tname) args
| None -> curry_app_list ~loc (bin_shape_lid ~loc lid) args)
| Ptyp_tuple typs -> shape_tuple ~loc (List.map typs ~f:traverse)
| Ptyp_var tvar ->
if allow_free_vars
then
[%expr Bin_prot.Shape.var [%e loc_string loc ~hide_loc] [%e shape_vid ~loc ~tvar]]
else expr_errorf ~loc "unexpected free type variable: '%s" tvar
| Ptyp_variant (rows, _, None) ->
shape_poly_variant
~loc
~hide_loc
(List.map rows ~f:(fun row -> traverse_row ~loc ~typ_for_error:typ row))
| Ptyp_poly (_, _)
| Ptyp_variant (_, _, Some _)
| Ptyp_any
| Ptyp_arrow _
| Ptyp_object _
| Ptyp_class _
| Ptyp_alias _
| Ptyp_package _
| Ptyp_extension _ ->
expr_errorf ~loc "unsupported type: %s" (string_of_core_type typ)
in
traverse
;;
let tvars_of_def (td : type_declaration)
: (string list, [ `Non_tvar of location ]) Result.t
=
let tvars, non_tvars =
List.partition_map td.ptype_params ~f:(fun (typ, _variance) ->
let loc = typ.ptyp_loc in
match typ with
| { ptyp_desc = Ptyp_var tvar; _ } -> First tvar
| _ -> Second (`Non_tvar loc))
in
match non_tvars with
| `Non_tvar loc :: _ -> Error (`Non_tvar loc)
| [] -> Ok tvars
;;
module Structure : sig
val gen : (structure, rec_flag * type_declaration list) Deriving.Generator.t
end = struct
let of_type = of_type ~allow_free_vars:true
let of_label_decs ~loc ~hide_loc ~context lds =
shape_record
~loc
(List.map lds ~f:(fun ld -> ld.pld_name.txt, of_type ~hide_loc ~context ld.pld_type))
;;
let of_kind ~loc ~hide_loc ~context (k : type_kind) : expression option =
match k with
| Ptype_record lds -> Some (of_label_decs ~loc ~hide_loc ~context lds)
| Ptype_variant cds ->
Some
(shape_variant
~loc
(List.map cds ~f:(fun cd ->
( cd.pcd_name.txt
, match cd.pcd_args with
| Pcstr_tuple args -> List.map args ~f:(of_type ~hide_loc ~context)
| Pcstr_record lds -> [ of_label_decs ~loc ~hide_loc ~context lds ] ))))
| Ptype_abstract -> None
| Ptype_open -> Some (expr_errorf ~loc "open types not supported")
;;
let expr_of_td ~loc ~hide_loc ~context (td : type_declaration) : expression option =
let expr =
match of_kind ~loc ~hide_loc ~context td.ptype_kind with
| Some e -> Some e
| None ->
(match td.ptype_manifest with
| None ->
Some (shape_variant ~loc [])
| Some manifest -> Some (of_type ~hide_loc ~context manifest))
in
expr
;;
let gen =
Deriving.Generator.make
Deriving.Args.(
empty
+> arg
"annotate"
(map ~f:string_literal (estring __) ||| map ~f:other_expression __)
+> arg
"annotate_provisionally"
(map ~f:string_literal (estring __) ||| map ~f:other_expression __)
+> arg
"basetype"
(map ~f:string_literal (estring __) ||| map ~f:other_expression __)
+> flag "hide_locations")
(fun ~loc
~path:_
(rec_flag, tds)
annotation_opt
annotation_provisionally_opt
basetype_opt
hide_loc ->
let tds = List.map tds ~f:name_type_params_in_td in
let context =
match rec_flag with
| Recursive -> Context.create tds
| Nonrecursive -> Context.create []
in
let mk_pat mk_ =
let pats =
List.map tds ~f:(fun td ->
let { Location.loc; txt = tname } = td.ptype_name in
let name = mk_ tname in
ppat_var ~loc (Loc.make name ~loc))
in
ppat_tuple ~loc pats
in
let () =
match annotation_provisionally_opt with
| Some _ ->
raise_errorf
~loc
"[~annotate_provisionally] was renamed to [~annotate]. Please use that."
| None -> ()
in
let () =
match annotation_opt, basetype_opt with
| Some _, Some _ ->
raise_errorf
~loc
"cannot write both [bin_shape ~annotate] and [bin_shape ~basetype]"
| _ -> ()
in
let annotate_f : expression -> expression =
match annotation_opt with
| None -> fun e -> e
| Some name ->
(match tds with
| [] | _ :: _ :: _ ->
fun _e ->
expr_errorf ~loc "unexpected [~annotate] on multi type-declaration"
| [ _ ] -> shape_annotate ~loc ~name)
in
let tagged_schemes =
List.filter_map tds ~f:(fun td ->
let { Location.loc; txt = tname } = td.ptype_name in
let body_opt = expr_of_td ~loc ~hide_loc ~context td in
match body_opt with
| None -> None
| Some body ->
(match tvars_of_def td with
| Error (`Non_tvar loc) ->
Some (expr_errorf ~loc "unexpected non-tvar in type params")
| Ok tvars ->
let formals = List.map tvars ~f:(fun tvar -> shape_vid ~loc ~tvar) in
[%expr [%e shape_tid ~loc ~tname], [%e elist ~loc formals], [%e body]]
|> fun x -> Some x))
in
let mk_exprs mk_init =
let exprs =
List.map tds ~f:(fun td ->
let { Location.loc; txt = tname } = td.ptype_name in
match tvars_of_def td with
| Error (`Non_tvar loc) ->
expr_errorf ~loc "unexpected non-tvar in type params"
| Ok tvars ->
let args = List.map tvars ~f:(fun tvar -> evar ~loc tvar) in
List.fold_right tvars ~init:(mk_init ~tname ~args) ~f:(fun tvar acc ->
[%expr fun [%p pvar ~loc tvar] -> [%e acc]]))
in
[%expr [%e pexp_tuple ~loc exprs]]
in
let expr =
match basetype_opt with
| Some uuid ->
(match tds with
| [] | _ :: _ :: _ ->
expr_errorf ~loc "unexpected [~basetype] on multi type-declaration"
| [ _ ] -> mk_exprs (fun ~tname:_ ~args -> shape_basetype ~loc ~uuid args))
| None ->
[%expr
let _group =
Bin_prot.Shape.group
[%e loc_string loc ~hide_loc]
[%e elist ~loc tagged_schemes]
in
[%e
mk_exprs (fun ~tname ~args ->
annotate_f (app_list ~loc (shape_top_app ~loc ~tname) args))]]
in
let bindings = [ value_binding ~loc ~pat:(mk_pat bin_shape_) ~expr ] in
let structure = [ pstr_value ~loc Nonrecursive bindings ] in
structure)
;;
end
module Signature : sig
val gen : (signature, rec_flag * type_declaration list) Deriving.Generator.t
end = struct
let of_td td : signature_item =
let td = name_type_params_in_td td in
let { Location.loc; txt = tname } = td.ptype_name in
let name = bin_shape_ tname in
match tvars_of_def td with
| Error (`Non_tvar loc) ->
psig_extension
~loc
(Location.Error.to_extension
(Location.Error.createf ~loc "%s" "unexpected non-tvar in type params"))
[]
| Ok tvars ->
let type_ =
List.fold_left tvars ~init:[%type: Bin_prot.Shape.t] ~f:(fun acc _ ->
[%type: Bin_prot.Shape.t -> [%t acc]])
in
psig_value ~loc (value_description ~loc ~name:(Loc.make name ~loc) ~type_ ~prim:[])
;;
let gen =
Deriving.Generator.make Deriving.Args.empty (fun ~loc:_ ~path:_ (_rec_flag, tds) ->
List.map tds ~f:of_td)
;;
end
let str_gen = Structure.gen
let sig_gen = Signature.gen
let shape_extension ~loc:_ ~hide_loc typ =
let context = Context.create [] in
let allow_free_vars = false in
of_type ~allow_free_vars ~hide_loc ~context typ
;;
let digest_extension ~loc ~hide_loc typ =
let loc = { loc with loc_ghost = true } in
[%expr
Bin_prot.Shape.Digest.to_hex
(Bin_prot.Shape.eval_to_digest [%e shape_extension ~loc ~hide_loc typ])]
;;