@@ -17,7 +17,7 @@ let pattern_has_constraint (type a) (pattern : a Typedtree.general_pattern) =
1717 pattern.pat_extra
1818
1919let structure_iterator hint_let_binding hint_pattern_binding
20- avoid_ghost_location typedtree range callback =
20+ _hint_function_params avoid_ghost_location typedtree range callback =
2121 let case_iterator hint_lhs (iterator : Iterator.iterator ) case =
2222 let () = log ~title: " case" " on case" in
2323 let () = if hint_lhs then iterator.pat iterator case.Typedtree. c_lhs in
@@ -136,21 +136,24 @@ let create_hint env typ loc =
136136 let position = loc.Location. loc_end in
137137 (position, label)
138138
139- let of_structure ~hint_let_binding ~hint_pattern_binding ~avoid_ghost_location
140- ~start ~stop structure =
139+ let of_structure ~hint_let_binding ~hint_pattern_binding ~hint_function_params
140+ ~avoid_ghost_location ~ start ~stop structure =
141141 let () =
142142 log ~title: " start" " %a" Logger. fmt (fun fmt ->
143143 Format. fprintf fmt
144- " Start on %s to %s with : let: %b, pat: %b, ghost: %b"
144+ " Start on %s to %s with : let: %b, pat: %b, function_param: %b, \
145+ ghost: %b"
145146 (Lexing. print_position () start)
146147 (Lexing. print_position () stop)
147- hint_let_binding hint_pattern_binding avoid_ghost_location)
148+ hint_let_binding hint_pattern_binding hint_function_params
149+ avoid_ghost_location)
148150 in
149151 let range = (start, stop) in
150152 let hints = ref [] in
151153 let () =
152154 structure_iterator hint_let_binding hint_pattern_binding
153- avoid_ghost_location structure range (fun env typ loc ->
155+ hint_function_params avoid_ghost_location structure range
156+ (fun env typ loc ->
154157 let () =
155158 log ~title: " hint" " Find hint %a" Logger. fmt (fun fmt ->
156159 Format. fprintf fmt " %s - %a"
0 commit comments