Skip to content

Commit 4efd65a

Browse files
committed
Compat
Signed-off-by: Paul-Elliot <[email protected]>
1 parent 8808baf commit 4efd65a

File tree

2 files changed

+26
-17
lines changed

2 files changed

+26
-17
lines changed

src/loader/compat.cppo.ml

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,3 +3,14 @@ let get_type_desc = Types.get_desc
33
#else
44
let get_type_desc t = t.Types.desc
55
#endif
6+
7+
(** Extract longident and constructor description from a pattern construct,
8+
when it is one. *)
9+
let get_pattern_construct_info (type a) : a Typedtree.pattern_desc -> _ = function
10+
#if OCAML_VERSION >= (4,13,0)
11+
Typedtree.Tpat_construct (l, { cstr_res; _ }, _, _)
12+
#else
13+
Tpat_construct (l, { cstr_res; _ }, _)
14+
#endif
15+
-> Some (l, cstr_res)
16+
| _ -> None

src/loader/occurrences.ml

Lines changed: 15 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -57,23 +57,21 @@ module Global_analysis = struct
5757
| _ -> ()
5858

5959
let pat poses (type a) : a Typedtree.general_pattern -> unit = function
60-
| {
61-
Typedtree.pat_desc = Tpat_construct (l, { cstr_res; _ }, _, _);
62-
pat_loc;
63-
_;
64-
} -> (
65-
let desc = Compat.get_type_desc cstr_res in
66-
match desc with
67-
| Types.Tconstr (p, _, _) -> (
68-
match childpath_of_path p with
69-
| None -> ()
70-
| Some ref_ ->
71-
poses :=
72-
( ConstructorPath (`Dot (ref_, Longident.last l.txt)),
73-
pos_of_loc pat_loc )
74-
:: !poses)
75-
| _ -> ())
76-
| _ -> ()
60+
| { Typedtree.pat_desc; pat_loc; _ } -> (
61+
match Compat.get_pattern_construct_info pat_desc with
62+
| Some (l, cstr_res) -> (
63+
let desc = Compat.get_type_desc cstr_res in
64+
match desc with
65+
| Types.Tconstr (p, _, _) -> (
66+
match childpath_of_path p with
67+
| None -> ()
68+
| Some ref_ ->
69+
poses :=
70+
( ConstructorPath (`Dot (ref_, Longident.last l.txt)),
71+
pos_of_loc pat_loc )
72+
:: !poses)
73+
| _ -> ())
74+
| None -> ())
7775

7876
let module_expr poses mod_expr =
7977
match mod_expr with

0 commit comments

Comments
 (0)