Skip to content

Commit 0d774b6

Browse files
committed
Added jmp-to-doc for constructors in patterns
Signed-off-by: Paul-Elliot <peada@free.fr>
1 parent 9d695bc commit 0d774b6

File tree

2 files changed

+24
-4
lines changed

2 files changed

+24
-4
lines changed

src/loader/occurrences.ml

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,25 @@ module Global_analysis = struct
5656
| _ -> ())
5757
| _ -> ()
5858

59+
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 = Types.get_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+
| _ -> ()
77+
5978
let module_expr poses mod_expr =
6079
match mod_expr with
6180
| { Typedtree.mod_desc = Tmod_ident (p, _); mod_loc; _ } -> (
@@ -102,6 +121,10 @@ let of_cmt (cmt : Cmt_format.cmt_infos) =
102121
Global_analysis.expr poses e;
103122
Tast_iterator.default_iterator.expr iterator e
104123
in
124+
let pat iterator e =
125+
Global_analysis.pat poses e;
126+
Tast_iterator.default_iterator.pat iterator e
127+
in
105128
let typ iterator ctyp_expr =
106129
Global_analysis.core_type poses ctyp_expr;
107130
Tast_iterator.default_iterator.typ iterator ctyp_expr
@@ -118,6 +141,7 @@ let of_cmt (cmt : Cmt_format.cmt_infos) =
118141
{
119142
Tast_iterator.default_iterator with
120143
expr;
144+
pat;
121145
module_expr;
122146
typ;
123147
module_type;

src/xref2/link.ml

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -186,10 +186,6 @@ let constructor_path :
186186
`Resolved Lang_of.(Path.resolved_constructor (empty ()) result)
187187
| Error e ->
188188
Errors.report ~what:(`Constructor_path cp) ~tools_error:e `Lookup;
189-
let _ =
190-
ignore e;
191-
failwith "todo"
192-
in
193189
p)
194190

195191
let class_type_path : Env.t -> Paths.Path.ClassType.t -> Paths.Path.ClassType.t

0 commit comments

Comments
 (0)