Skip to content

Commit f0cb11d

Browse files
committed
refactor: get rid of stdune from code generator
Signed-off-by: Rudi Grinberg <[email protected]> <!-- ps-id: eb2c14ee-02d9-45df-a29a-3d85fca1759b --> Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 5b6fd4b commit f0cb11d

File tree

10 files changed

+164
-58
lines changed

10 files changed

+164
-58
lines changed

lsp/bin/cinaps.ml

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ let preprocess_metamodel =
77
method! or_ path (types : Metamodel.type_ list) =
88
match
99
List.filter_map types ~f:(function
10-
| Literal (Record []) -> None
10+
| Metamodel.Literal (Record []) -> None
1111
| _ as t -> Some (self#type_ path t))
1212
with
1313
| [] -> assert false
@@ -17,10 +17,13 @@ let preprocess_metamodel =
1717
| Top (Alias s) when s.name = "TextDocumentContentChangeEvent" ->
1818
let t =
1919
let union_fields l1 l2 ~f =
20-
let of_map =
21-
String.Map.of_list_map_exn ~f:(fun (x : Metamodel.property) -> x.name, x)
20+
let of_map xs =
21+
List.map xs ~f:(fun (x : Metamodel.property) -> x.name, x)
22+
|> String.Map.of_list
2223
in
23-
String.Map.merge (of_map l1) (of_map l2) ~f |> String.Map.values
24+
String.Map.merge (of_map l1) (of_map l2) ~f
25+
|> String.Map.bindings
26+
|> List.map ~f:snd
2427
in
2528
union_fields f1 f2 ~f:(fun k t1 t2 ->
2629
if k = "text"
@@ -81,8 +84,9 @@ let expand_superclasses db (m : Metamodel.t) =
8184
let structures =
8285
let uniquify_fields fields =
8386
List.fold_left fields ~init:String.Map.empty ~f:(fun acc (f : Metamodel.property) ->
84-
String.Map.set acc f.name f)
85-
|> String.Map.values
87+
String.Map.add acc ~key:f.name ~data:f)
88+
|> String.Map.bindings
89+
|> List.map ~f:snd
8690
in
8791
let rec fields_of_type (t : Metamodel.type_) =
8892
match t with

lsp/bin/dune

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
(test
44
(name test_metamodel)
55
(modules test_metamodel)
6-
(libraries stdune yojson lsp_gen)
6+
(libraries yojson lsp_gen)
77
(deps metamodel/metaModel.json)
88
(action
99
(run ./test_metamodel.exe %{deps})))
@@ -13,4 +13,4 @@
1313
(instrumentation
1414
(backend bisect_ppx))
1515
(modules :standard \ test_metamodel)
16-
(libraries stdune dyn pp yojson))
16+
(libraries dyn pp yojson))

lsp/bin/import.ml

Lines changed: 69 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,70 @@
1-
include struct
2-
open Stdune
3-
module List = List
4-
module Id = Id
5-
module String = String
6-
module Code_error = Code_error
7-
module Comparable = Comparable
8-
module Top_closure = Top_closure
9-
module Poly = Poly
10-
module Option = Option
11-
12-
let sprintf = sprintf
1+
let sprintf = Printf.sprintf
2+
3+
module Option = struct
4+
include Option
5+
6+
let map t ~f = Option.map f t
7+
8+
let value_exn = function
9+
| None -> assert false
10+
| Some s -> s
11+
;;
12+
end
13+
14+
module List = struct
15+
include ListLabels
16+
17+
type ('a, 'b) skip_or_either =
18+
| Skip
19+
| Left of 'a
20+
| Right of 'b
21+
22+
let rev_filter_partition_map =
23+
let rec loop l accl accr ~f =
24+
match l with
25+
| [] -> accl, accr
26+
| x :: l ->
27+
(match f x with
28+
| Skip -> loop l accl accr ~f
29+
| Left y -> loop l (y :: accl) accr ~f
30+
| Right y -> loop l accl (y :: accr) ~f)
31+
in
32+
fun l ~f -> loop l [] [] ~f
33+
;;
34+
35+
let filter_partition_map l ~f =
36+
let l, r = rev_filter_partition_map l ~f in
37+
rev l, rev r
38+
;;
39+
end
40+
41+
module String = struct
42+
include StringLabels
43+
44+
let to_dyn = Dyn.string
45+
46+
module Map = struct
47+
include MoreLabels.Map.Make (String)
48+
49+
let of_list_reducei xs ~f =
50+
List.fold_left xs ~init:empty ~f:(fun map (k, v) ->
51+
update map ~key:k ~f:(function
52+
| None -> Some v
53+
| Some v' -> Some (f k v v')))
54+
;;
55+
56+
let of_list_map_exn xs ~f = List.map xs ~f |> of_list
57+
let union_exn x y = union ~f:(fun _ _ _ -> assert false) x y
58+
end
59+
end
60+
61+
module Code_error = struct
62+
let raise name data =
63+
invalid_arg (sprintf "%s %s" name (Dyn.to_string (Dyn.record data)))
64+
;;
65+
end
66+
67+
module Poly = struct
68+
let equal = Stdlib.( = )
69+
let compare = Stdlib.compare
1370
end

lsp/bin/metamodel/metamodel.ml

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
open Stdune
1+
open Import
22

33
type doc =
44
{ since : string option
@@ -113,7 +113,7 @@ let fields = function
113113
;;
114114

115115
let field ?default (name : string) p fields =
116-
match List.assoc fields name with
116+
match List.assoc_opt name fields with
117117
| Some f -> p f
118118
| None ->
119119
(match default with
@@ -122,7 +122,7 @@ let field ?default (name : string) p fields =
122122
;;
123123

124124
let field_o name p fields =
125-
match List.assoc fields name with
125+
match List.assoc_opt name fields with
126126
| None -> None
127127
| Some f -> Some (p f)
128128
;;
@@ -137,7 +137,7 @@ let literal lit json = if not (Poly.equal json lit) then error "unexpected liter
137137
let enum variants json =
138138
match json with
139139
| `String s ->
140-
(match List.assoc variants s with
140+
(match List.assoc_opt s variants with
141141
| None -> error "not a valid enum value" json
142142
| Some v -> v)
143143
| _ -> error "not a valid enum value" json
@@ -370,7 +370,7 @@ module Entity = struct
370370
String.Map.union_exn structures enumerations |> String.Map.union_exn typeAliases
371371
;;
372372

373-
let find t x = String.Map.find_exn t x
373+
let find t x = String.Map.find x t
374374
end
375375
end
376376

lsp/bin/ocaml/json_gen.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ let json_error_pat msg =
3434
;;
3535

3636
let is_json_constr (constr : Type.constr) =
37-
List.mem [ "String"; "Int"; "Bool" ] constr.name ~equal:String.equal
37+
List.mem ~set:[ "String"; "Int"; "Bool" ] constr.name
3838
;;
3939

4040
module Name = struct

lsp/bin/ocaml/ml.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -409,7 +409,7 @@ module Expr = struct
409409

410410
let pp_constr f { tag; poly; args } =
411411
let tag =
412-
let tag = String.capitalize tag in
412+
let tag = String.capitalize_ascii tag in
413413
Pp.verbatim (if poly then "`" ^ tag else tag)
414414
in
415415
match args with

lsp/bin/ocaml/ocaml.ml

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -79,9 +79,7 @@ module Expanded = struct
7979
| None -> init
8080
| Some data ->
8181
let new_record = { f with data } in
82-
if List.mem ~equal:Poly.equal init new_record
83-
then init
84-
else new_record :: init)
82+
if List.mem ~set:init new_record then init else new_record :: init)
8583
in
8684
super#field f ~init
8785
end
@@ -274,18 +272,18 @@ module Entities = struct
274272
type t = (Ident.t * Resolved.t) list
275273

276274
let find db e : _ Named.t =
277-
match List.assoc db e with
275+
match List.assoc_opt e db with
278276
| Some s -> s
279277
| None -> Code_error.raise "Entities.find: unable to find" [ "e", Ident.to_dyn e ]
280278
;;
281279

282280
let of_map map ts =
283-
List.map ts ~f:(fun (r : Resolved.t) -> String.Map.find_exn map r.name, r)
281+
List.map ts ~f:(fun (r : Resolved.t) -> String.Map.find r.name map, r)
284282
;;
285283

286284
let rev_find (db : t) (resolved : Resolved.t) : Ident.t =
287285
match
288-
List.filter_map db ~f:(fun (id, r) ->
286+
List.filter_map db ~f:(fun (id, (r : Resolved.t)) ->
289287
if r.name = resolved.name then Some id else None)
290288
with
291289
| [] -> Code_error.raise "rev_find: resolved not found" []
@@ -327,17 +325,17 @@ end = struct
327325
[ Prim.Null; String; Bool; Number; Object; List ]
328326
|> List.map ~f:(fun s -> Resolved.Ident s)
329327
in
330-
fun set -> List.for_all constrs ~f:(fun e -> List.mem set e ~equal:Poly.equal)
328+
fun set -> List.for_all constrs ~f:(List.mem ~set)
331329
;;
332330

333331
let id = Type.name "Jsonrpc.Id.t"
334332

335333
let is_same_as_id =
336-
let sort = List.sort ~compare:Poly.compare in
334+
let sort = List.sort ~cmp:Poly.compare in
337335
let constrs =
338336
[ Prim.String; Number ] |> List.map ~f:(fun s -> Resolved.Ident s) |> sort
339337
in
340-
fun cs -> List.equal ( = ) constrs (sort cs)
338+
fun cs -> List.equal ~eq:( = ) constrs (sort cs)
341339
;;
342340

343341
(* Any type that includes null needs to be extracted to be converted to an
@@ -585,7 +583,7 @@ end = struct
585583
let literal_wrapper =
586584
match literal_wrapper with
587585
| None -> []
588-
| Some { field_name; literal_value } ->
586+
| Some { Mapper.field_name; literal_value } ->
589587
Json_gen.make_literal_wrapper_conv
590588
~field_name
591589
~literal_value
@@ -626,7 +624,7 @@ let resolve_typescript (ts : Unresolved.t list) =
626624
let db = Entities.of_map db ts in
627625
match
628626
let idents = new name_idents in
629-
Ident.Top_closure.top_closure
627+
Ident.top_closure
630628
ts
631629
~key:(fun x -> Entities.rev_find db x)
632630
~deps:(fun x -> idents#t x ~init:[] |> List.map ~f:(Entities.find db))
@@ -640,7 +638,7 @@ let resolve_typescript (ts : Unresolved.t list) =
640638
let of_resolved_typescript db (ts : Resolved.t list) =
641639
let simple_enums, everything_else =
642640
List.filter_partition_map ts ~f:(fun (t : Resolved.t) ->
643-
if List.mem skipped_ts_decls t.name ~equal:String.equal
641+
if List.mem ~set:skipped_ts_decls t.name
644642
then Skip
645643
else (
646644
match t.data with
@@ -650,7 +648,7 @@ let of_resolved_typescript db (ts : Resolved.t list) =
650648
let simple_enums =
651649
List.map simple_enums ~f:(fun (t : _ Named.t) ->
652650
(* "open" enums need an `Other constructor *)
653-
let allow_other = List.mem ~equal:String.equal with_custom_values t.name in
651+
let allow_other = List.mem ~set:with_custom_values t.name in
654652
let data =
655653
List.filter_map t.data ~f:(fun (constr, v) ->
656654
match (v : Ts_types.Enum.case) with

lsp/bin/typescript/ts_types.ml

Lines changed: 56 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -262,7 +262,19 @@ module Unresolved = struct
262262
end
263263

264264
module Ident = struct
265-
module Id = Stdune.Id.Make ()
265+
module Id = struct
266+
type t = int
267+
268+
let counter = ref 0
269+
270+
let gen () =
271+
incr counter;
272+
!counter
273+
;;
274+
275+
let compare = Int.compare
276+
let to_dyn = Dyn.int
277+
end
266278

267279
module T = struct
268280
type t =
@@ -282,9 +294,44 @@ module Ident = struct
282294

283295
let make name = { name; id = Id.gen () }
284296

285-
module C = Comparable.Make (T)
286-
module Set = C.Set
287-
module Top_closure = Top_closure.Make (Set) (Stdune.Monad.Id)
297+
module Keys = struct
298+
include MoreLabels.Set.Make (T)
299+
300+
let add x y = add y x
301+
let mem x y = mem y x
302+
end
303+
304+
let top_closure ~key ~deps elements =
305+
let rec loop res visited elt ~temporarily_marked =
306+
let key = key elt in
307+
if Keys.mem temporarily_marked key
308+
then Error [ elt ]
309+
else if not (Keys.mem visited key)
310+
then (
311+
let visited = Keys.add visited key in
312+
let temporarily_marked = Keys.add temporarily_marked key in
313+
deps elt
314+
|> iter_elts res visited ~temporarily_marked
315+
|> function
316+
| Error l -> Error (elt :: l)
317+
| Ok (res, visited) ->
318+
let res = elt :: res in
319+
Ok (res, visited))
320+
else Ok (res, visited)
321+
and iter_elts res visited elts ~temporarily_marked =
322+
match elts with
323+
| [] -> Ok (res, visited)
324+
| elt :: elts ->
325+
loop res visited elt ~temporarily_marked
326+
|> (function
327+
| Error _ as result -> result
328+
| Ok (res, visited) -> iter_elts res visited elts ~temporarily_marked)
329+
in
330+
iter_elts [] Keys.empty elements ~temporarily_marked:Keys.empty
331+
|> function
332+
| Ok (res, _visited) -> Ok (List.rev res)
333+
| Error elts -> Error elts
334+
;;
288335
end
289336

290337
module Prim = struct
@@ -345,15 +392,15 @@ let subst unresolved =
345392
method inside s = {<inside = Some s>}
346393

347394
method resolve n =
348-
match String.Map.find params n with
395+
match String.Map.find_opt n params with
349396
| Some [] -> assert false
350397
| Some (x :: _) -> `Resolved x
351398
| None ->
352-
if inside = Some n then `Self else `Unresolved (String.Map.find_exn unresolved n)
399+
if inside = Some n then `Self else `Unresolved (String.Map.find n unresolved)
353400

354401
method push x y =
355402
let params =
356-
String.Map.update params x ~f:(function
403+
String.Map.update params ~key:x ~f:(function
357404
| None -> Some [ y ]
358405
| Some [] -> assert false
359406
| Some (y' :: xs) -> if y = y' then Some xs else Some (y :: y' :: xs))
@@ -362,9 +409,9 @@ let subst unresolved =
362409

363410
method pop x =
364411
let params =
365-
String.Map.update params x ~f:(function
412+
String.Map.update params ~key:x ~f:(function
366413
| None ->
367-
ignore (String.Map.find_exn params x);
414+
ignore (String.Map.find x params);
368415
None
369416
| Some [] -> assert false
370417
| Some (_ :: xs) -> Some xs)

0 commit comments

Comments
 (0)