File tree Expand file tree Collapse file tree 5 files changed +38
-9
lines changed Expand file tree Collapse file tree 5 files changed +38
-9
lines changed Original file line number Diff line number Diff line change @@ -14,7 +14,7 @@ let code_action pipeline doc (params : CodeActionParams.t) =
1414 let src = Document. source doc in
1515 Compl. prefix_of_position ~short_path: false src pos
1616 in
17- if not (Merlin_analysis. Typed_hole. can_be_hole prefix)
17+ if not (Typed_hole. can_be_hole prefix)
1818 then None
1919 else (
2020 let structures =
@@ -25,7 +25,7 @@ let code_action pipeline doc (params : CodeActionParams.t) =
2525 let pos = Mpipeline. get_lexing_pos pipeline pos in
2626 Mbrowse. enclosing pos [ Mbrowse. of_typedtree typedtree ]
2727 in
28- if not (Merlin_analysis. Typed_hole. is_a_hole structures)
28+ if not (Typed_hole. is_a_hole structures)
2929 then None
3030 else (
3131 (* ocaml-lsp can provide [Construct] values as completion entries, so
Original file line number Diff line number Diff line change @@ -315,7 +315,7 @@ let complete
315315 let * item = completion_item_capability in
316316 item.deprecatedSupport)
317317 in
318- if not (Merlin_analysis. Typed_hole. can_be_hole prefix)
318+ if not (Typed_hole. can_be_hole prefix)
319319 then Complete_by_prefix. complete merlin prefix pos ~resolve ~deprecated
320320 else (
321321 let reindex_sortText completion_items =
Original file line number Diff line number Diff line change @@ -29,11 +29,7 @@ let compute (state : State.t) { InlayHintParams.range; textDocument = { uri }; _
2929 c.hint_pattern_variables)
3030 |> Option. value ~default: false
3131 in
32- let hint_function_params =
33- Option. map state.configuration.data.inlay_hints ~f: (fun c ->
34- c.hint_function_params)
35- |> Option. value ~default: false
36- in
32+ (* NOTE: hint_function_params is not available in merlin-lib 4.18 *)
3733 Document.Merlin. with_pipeline_exn ~name: " inlay-hints" doc (fun pipeline ->
3834 let start = range.start |> Position. logical
3935 and stop = range.end_ |> Position. logical in
@@ -43,7 +39,6 @@ let compute (state : State.t) { InlayHintParams.range; textDocument = { uri }; _
4339 , stop
4440 , hint_let_bindings
4541 , hint_pattern_variables
46- , hint_function_params
4742 , not inside_test )
4843 in
4944 let hints = Query_commands. dispatch pipeline command in
Original file line number Diff line number Diff line change 11open Import
22
3+ let syntax_repr = " _"
4+ let can_be_hole s = String. equal syntax_repr s
5+
6+ (* the pattern matching below is taken and modified (minimally, to adapt the
7+ return type) from [Query_commands.dispatch]'s [Construct] branch;
8+
9+ If we directly dispatched [Construct] command to merlin, we'd be doing
10+ useless computations: we need info whether the expression at the cursor is a
11+ hole, we don't need constructed expressions yet.
12+
13+ Ideally, merlin should return a callback [option], which is [Some] when the
14+ context is applicable. *)
15+ let is_a_hole = function
16+ | (_, Browse_raw. Module_expr { mod_desc = Tmod_hole ; _ }) :: (_, _) :: _
17+ | (_ , Browse_raw. Expression { exp_desc = Texp_hole ; _ } ) :: _ -> true
18+ | [] | (_ , _ ) :: _ -> false
19+ ;;
20+
321let in_range range holes =
422 match range with
523 | None -> holes
Original file line number Diff line number Diff line change 1+ (* * This module should be used to work with typed holes. The main goal is to
2+ hide syntactic representation of a typed hole, which may change in future *)
3+
4+ (* * checks whether the current string matches the syntax representation of a
5+ typed hole *)
6+ val can_be_hole : string -> bool
7+
8+ (* * [is_a_hole nodes] checks whether the leaf node [1] is a typed hole
9+
10+ Note: this function is extracted from merlin sources handling [Construct]
11+ command in [merlin/src/frontend/query_commands.ml]
12+
13+ [1] leaf node is the head of the list, as
14+ [Mbrowse.t = (Env.t * Browse_raw.node) list]*)
15+ val is_a_hole : (Ocaml_typing.Env .t * Merlin_specific.Browse_raw .node ) list -> bool
16+
117val find
218 : range:Range. t option
319 -> position:Position. t
You can’t perform that action at this time.
0 commit comments