Skip to content

Commit 3126a9b

Browse files
committed
Sync latest syntax.
1 parent cb8eba6 commit 3126a9b

File tree

200 files changed

+56350
-22912
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

200 files changed

+56350
-22912
lines changed

analysis/reanalyze/src/Paths.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
open Common
2-
module StringMap = Map.Make (String)
2+
module StringMap = Ext_json_types.StringMap
33

44
let bsconfig = "bsconfig.json"
55

analysis/src/ProcessExtra.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ let extraForCmt ~(iterator : Tast_iterator.iterator)
107107
| Partial_signature_item str -> iterator.signature_item iterator str
108108
| Partial_expression expression -> iterator.expr iterator expression
109109
| Partial_pattern pattern -> iterator.pat iterator pattern
110-
| Partial_class_expr () -> ()
110+
| Partial_class_expr _ -> ()
111111
| Partial_module_type module_type ->
112112
iterator.module_type iterator module_type
113113
| Partial_structure _ | Partial_structure_item _ -> ())

analysis/tests/src/expected/Completion.res.txt

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -889,13 +889,13 @@ Completable: Cpath Value[FAO, forAutoObject]["forAutoLabel"].""
889889
"label": "forAuto",
890890
"kind": 5,
891891
"tags": [],
892-
"detail": "forAuto: ForAuto.t\n\ntype forAutoRecord = {\n forAuto: ForAuto.t,\n something: option<int>,\n}",
892+
"detail": "forAuto: ForAuto.t\n\ntype forAutoRecord = {forAuto: ForAuto.t, something: int}",
893893
"documentation": null
894894
}, {
895895
"label": "something",
896896
"kind": 5,
897897
"tags": [],
898-
"detail": "something: option<int>\n\ntype forAutoRecord = {\n forAuto: ForAuto.t,\n something: option<int>,\n}",
898+
"detail": "something: option<int>\n\ntype forAutoRecord = {forAuto: ForAuto.t, something: int}",
899899
"documentation": null
900900
}]
901901

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
(**************************************************************************)
2+
(* *)
3+
(* OCaml *)
4+
(* *)
5+
(* Damien Doligez, projet Gallium, INRIA Rocquencourt *)
6+
(* *)
7+
(* Copyright 2007 Institut National de Recherche en Informatique et *)
8+
(* en Automatique. *)
9+
(* *)
10+
(* All rights reserved. This file is distributed under the terms of *)
11+
(* the GNU Lesser General Public License version 2.1, with the *)
12+
(* special exception on linking described in the file LICENSE. *)
13+
(* *)
14+
(**************************************************************************)
15+
16+
(* Data types for annotations (Stypes.ml) *)
17+
18+
type call = Tail | Stack | Inline;;
19+
20+
type ident =
21+
| Iref_internal of Location.t (* defining occurrence *)
22+
| Iref_external
23+
| Idef of Location.t (* scope *)
24+
;;
Lines changed: 127 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,127 @@
1+
(**************************************************************************)
2+
(* *)
3+
(* OCaml *)
4+
(* *)
5+
(* Pierre Chambart, OCamlPro *)
6+
(* Mark Shinwell and Leo White, Jane Street Europe *)
7+
(* *)
8+
(* Copyright 2015--2016 OCamlPro SAS *)
9+
(* Copyright 2015--2016 Jane Street Group LLC *)
10+
(* *)
11+
(* All rights reserved. This file is distributed under the terms of *)
12+
(* the GNU Lesser General Public License version 2.1, with the *)
13+
(* special exception on linking described in the file LICENSE. *)
14+
(* *)
15+
(**************************************************************************)
16+
17+
let fatal err =
18+
prerr_endline err;
19+
exit 2
20+
21+
module Make (S : sig
22+
module Key : sig
23+
type t
24+
val of_string : string -> t
25+
module Map : Map.S with type key = t
26+
end
27+
28+
module Value : sig
29+
type t
30+
val of_string : string -> t
31+
end
32+
end) = struct
33+
type parsed = {
34+
base_default : S.Value.t;
35+
base_override : S.Value.t S.Key.Map.t;
36+
user_default : S.Value.t option;
37+
user_override : S.Value.t S.Key.Map.t;
38+
}
39+
40+
let default v =
41+
{ base_default = v;
42+
base_override = S.Key.Map.empty;
43+
user_default = None;
44+
user_override = S.Key.Map.empty; }
45+
46+
let set_base_default value t =
47+
{ t with base_default = value }
48+
49+
let add_base_override key value t =
50+
{ t with base_override = S.Key.Map.add key value t.base_override }
51+
52+
let reset_base_overrides t =
53+
{ t with base_override = S.Key.Map.empty }
54+
55+
let set_user_default value t =
56+
{ t with user_default = Some value }
57+
58+
let add_user_override key value t =
59+
{ t with user_override = S.Key.Map.add key value t.user_override }
60+
61+
exception Parse_failure of exn
62+
63+
let parse_exn str ~update =
64+
(* Is the removal of empty chunks really relevant here? *)
65+
(* (It has been added to mimic the old Misc.String.split.) *)
66+
let values = String.split_on_char ',' str |> List.filter ((<>) "") in
67+
let parsed =
68+
List.fold_left (fun acc value ->
69+
match String.index value '=' with
70+
| exception Not_found ->
71+
begin match S.Value.of_string value with
72+
| value -> set_user_default value acc
73+
| exception exn -> raise (Parse_failure exn)
74+
end
75+
| equals ->
76+
let key_value_pair = value in
77+
let length = String.length key_value_pair in
78+
assert (equals >= 0 && equals < length);
79+
if equals = 0 then begin
80+
raise (Parse_failure (
81+
Failure "Missing key in argument specification"))
82+
end;
83+
let key =
84+
let key = String.sub key_value_pair 0 equals in
85+
try S.Key.of_string key
86+
with exn -> raise (Parse_failure exn)
87+
in
88+
let value =
89+
let value =
90+
String.sub key_value_pair (equals + 1) (length - equals - 1)
91+
in
92+
try S.Value.of_string value
93+
with exn -> raise (Parse_failure exn)
94+
in
95+
add_user_override key value acc)
96+
!update
97+
values
98+
in
99+
update := parsed
100+
101+
let parse str help_text update =
102+
match parse_exn str ~update with
103+
| () -> ()
104+
| exception (Parse_failure exn) ->
105+
fatal (Printf.sprintf "%s: %s" (Printexc.to_string exn) help_text)
106+
107+
type parse_result =
108+
| Ok
109+
| Parse_failed of exn
110+
111+
let parse_no_error str update =
112+
match parse_exn str ~update with
113+
| () -> Ok
114+
| exception (Parse_failure exn) -> Parse_failed exn
115+
116+
let get ~key parsed =
117+
match S.Key.Map.find key parsed.user_override with
118+
| value -> value
119+
| exception Not_found ->
120+
match parsed.user_default with
121+
| Some value -> value
122+
| None ->
123+
match S.Key.Map.find key parsed.base_override with
124+
| value -> value
125+
| exception Not_found -> parsed.base_default
126+
127+
end
Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,63 @@
1+
(**************************************************************************)
2+
(* *)
3+
(* OCaml *)
4+
(* *)
5+
(* Pierre Chambart, OCamlPro *)
6+
(* Mark Shinwell and Leo White, Jane Street Europe *)
7+
(* *)
8+
(* Copyright 2015--2016 OCamlPro SAS *)
9+
(* Copyright 2015--2016 Jane Street Group LLC *)
10+
(* *)
11+
(* All rights reserved. This file is distributed under the terms of *)
12+
(* the GNU Lesser General Public License version 2.1, with the *)
13+
(* special exception on linking described in the file LICENSE. *)
14+
(* *)
15+
(**************************************************************************)
16+
17+
(** Decipher command line arguments of the form
18+
<value> | <key>=<value>[,...]
19+
(as used for example for the specification of inlining parameters
20+
varying by simplification round).
21+
*)
22+
23+
module Make (S : sig
24+
module Key : sig
25+
type t
26+
27+
(** The textual representation of a key must not contain '=' or ','. *)
28+
val of_string : string -> t
29+
30+
module Map : Map.S with type key = t
31+
end
32+
33+
module Value : sig
34+
type t
35+
36+
(** The textual representation of a value must not contain ','. *)
37+
val of_string : string -> t
38+
end
39+
end) : sig
40+
type parsed
41+
42+
val default : S.Value.t -> parsed
43+
44+
val set_base_default : S.Value.t -> parsed -> parsed
45+
46+
val add_base_override : S.Key.t -> S.Value.t -> parsed -> parsed
47+
48+
val reset_base_overrides : parsed -> parsed
49+
50+
val set_user_default : S.Value.t -> parsed -> parsed
51+
52+
val add_user_override : S.Key.t -> S.Value.t -> parsed -> parsed
53+
54+
val parse : string -> string -> parsed ref -> unit
55+
56+
type parse_result =
57+
| Ok
58+
| Parse_failed of exn
59+
60+
val parse_no_error : string -> parsed ref -> parse_result
61+
62+
val get : key:S.Key.t -> parsed -> S.Value.t
63+
end

analysis/vendor/compiler-libs-406/ast_helper.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -239,6 +239,7 @@ module Sig = struct
239239
let modtype ?loc a = mk ?loc (Psig_modtype a)
240240
let open_ ?loc a = mk ?loc (Psig_open a)
241241
let include_ ?loc a = mk ?loc (Psig_include a)
242+
let class_ ?loc a = mk ?loc (Psig_class a)
242243
let class_type ?loc a = mk ?loc (Psig_class_type a)
243244
let extension ?loc ?(attrs = []) a = mk ?loc (Psig_extension (a, attrs))
244245
let attribute ?loc a = mk ?loc (Psig_attribute a)
@@ -262,6 +263,7 @@ module Str = struct
262263
let rec_module ?loc a = mk ?loc (Pstr_recmodule a)
263264
let modtype ?loc a = mk ?loc (Pstr_modtype a)
264265
let open_ ?loc a = mk ?loc (Pstr_open a)
266+
let class_ ?loc a = mk ?loc (Pstr_class a)
265267
let class_type ?loc a = mk ?loc (Pstr_class_type a)
266268
let include_ ?loc a = mk ?loc (Pstr_include a)
267269
let extension ?loc ?(attrs = []) a = mk ?loc (Pstr_extension (a, attrs))
@@ -342,7 +344,7 @@ module Cf = struct
342344
pcf_attributes = add_docs_attrs docs attrs;
343345
}
344346

345-
347+
let inherit_ ?loc ?attrs a b c = mk ?loc ?attrs (Pcf_inherit (a, b, c))
346348
let val_ ?loc ?attrs a b c = mk ?loc ?attrs (Pcf_val (a, b, c))
347349
let method_ ?loc ?attrs a b c = mk ?loc ?attrs (Pcf_method (a, b, c))
348350
let constraint_ ?loc ?attrs a b = mk ?loc ?attrs (Pcf_constraint (a, b))

analysis/vendor/compiler-libs-406/ast_helper.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -267,6 +267,7 @@ module Sig:
267267
val modtype: ?loc:loc -> module_type_declaration -> signature_item
268268
val open_: ?loc:loc -> open_description -> signature_item
269269
val include_: ?loc:loc -> include_description -> signature_item
270+
val class_: ?loc:loc -> class_description list -> signature_item
270271
val class_type: ?loc:loc -> class_type_declaration list -> signature_item
271272
val extension: ?loc:loc -> ?attrs:attrs -> extension -> signature_item
272273
val attribute: ?loc:loc -> attribute -> signature_item
@@ -288,6 +289,7 @@ module Str:
288289
val rec_module: ?loc:loc -> module_binding list -> structure_item
289290
val modtype: ?loc:loc -> module_type_declaration -> structure_item
290291
val open_: ?loc:loc -> open_description -> structure_item
292+
val class_: ?loc:loc -> class_declaration list -> structure_item
291293
val class_type: ?loc:loc -> class_type_declaration list -> structure_item
292294
val include_: ?loc:loc -> include_declaration -> structure_item
293295
val extension: ?loc:loc -> ?attrs:attrs -> extension -> structure_item
@@ -401,6 +403,8 @@ module Cf:
401403
class_field
402404
val attr: class_field -> attribute -> class_field
403405

406+
val inherit_: ?loc:loc -> ?attrs:attrs -> override_flag -> class_expr ->
407+
str option -> class_field
404408
val val_: ?loc:loc -> ?attrs:attrs -> str -> mutable_flag ->
405409
class_field_kind -> class_field
406410
val method_: ?loc:loc -> ?attrs:attrs -> str -> private_flag ->

analysis/vendor/compiler-libs-406/ast_iterator.ml

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,8 @@ type iterator = {
2929
attributes: iterator -> attribute list -> unit;
3030
case: iterator -> case -> unit;
3131
cases: iterator -> case list -> unit;
32+
class_declaration: iterator -> class_declaration -> unit;
33+
class_description: iterator -> class_description -> unit;
3234
class_expr: iterator -> class_expr -> unit;
3335
class_field: iterator -> class_field -> unit;
3436
class_signature: iterator -> class_signature -> unit;
@@ -248,7 +250,7 @@ module MT = struct
248250
| Psig_modtype x -> sub.module_type_declaration sub x
249251
| Psig_open x -> sub.open_description sub x
250252
| Psig_include x -> sub.include_description sub x
251-
| Psig_class () -> ()
253+
| Psig_class l -> List.iter (sub.class_description sub) l
252254
| Psig_class_type l ->
253255
List.iter (sub.class_type_declaration sub) l
254256
| Psig_extension (x, attrs) ->
@@ -291,7 +293,7 @@ module M = struct
291293
| Pstr_recmodule l -> List.iter (sub.module_binding sub) l
292294
| Pstr_modtype x -> sub.module_type_declaration sub x
293295
| Pstr_open x -> sub.open_description sub x
294-
| Pstr_class () -> ()
296+
| Pstr_class l -> List.iter (sub.class_declaration sub) l
295297
| Pstr_class_type l ->
296298
List.iter (sub.class_type_declaration sub) l
297299
| Pstr_include x -> sub.include_declaration sub x
@@ -443,7 +445,7 @@ module CE = struct
443445
sub.location sub loc;
444446
sub.attributes sub attrs;
445447
match desc with
446-
| Pcf_inherit () -> ()
448+
| Pcf_inherit (_o, ce, _s) -> sub.class_expr sub ce
447449
| Pcf_val (s, _m, k) -> iter_loc sub s; iter_kind sub k
448450
| Pcf_method (s, _p, k) ->
449451
iter_loc sub s; iter_kind sub k
@@ -479,6 +481,8 @@ let default_iterator =
479481
signature_item = MT.iter_signature_item;
480482
module_type = MT.iter;
481483
with_constraint = MT.iter_with_constraint;
484+
class_declaration =
485+
(fun this -> CE.class_infos this (this.class_expr this));
482486
class_expr = CE.iter;
483487
class_field = CE.iter_field;
484488
class_structure = CE.iter_structure;
@@ -487,6 +491,8 @@ let default_iterator =
487491
class_signature = CT.iter_signature;
488492
class_type_declaration =
489493
(fun this -> CE.class_infos this (this.class_type this));
494+
class_description =
495+
(fun this -> CE.class_infos this (this.class_type this));
490496
type_declaration = T.iter_type_declaration;
491497
type_kind = T.iter_type_kind;
492498
typ = T.iter;

analysis/vendor/compiler-libs-406/ast_iterator.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,8 @@ type iterator = {
2626
attributes: iterator -> attribute list -> unit;
2727
case: iterator -> case -> unit;
2828
cases: iterator -> case list -> unit;
29+
class_declaration: iterator -> class_declaration -> unit;
30+
class_description: iterator -> class_description -> unit;
2931
class_expr: iterator -> class_expr -> unit;
3032
class_field: iterator -> class_field -> unit;
3133
class_signature: iterator -> class_signature -> unit;

0 commit comments

Comments
 (0)