Skip to content

Commit

Permalink
_
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed May 11, 2024
1 parent eb0c07d commit a05af8f
Show file tree
Hide file tree
Showing 5 changed files with 38 additions and 27 deletions.
11 changes: 5 additions & 6 deletions ocaml-lsp-server/src/check_for_comments.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,12 @@ let position_in_comment ~position ~merlin =
let start = Position.of_lexical_position loc.loc_start in
let end_ = Position.of_lexical_position loc.loc_end in
match Option.both start end_ with
| Some (start, end_) ->
| Some (start, end_) -> (
let range = Range.create ~start ~end_ in
(match Position.compare_inclusion position range with
| `Inside -> true
| `Outside _ -> false)
match Position.compare_inclusion position range with
| `Inside -> true
| `Outside _ -> false)
| None -> false
in
Document.Merlin.with_pipeline_exn ~name:"get-comments" merlin (fun pipeline ->
Mpipeline.reader_comments pipeline |> List.exists ~f:loc_contains_position)
;;
Mpipeline.reader_comments pipeline |> List.exists ~f:loc_contains_position)
3 changes: 2 additions & 1 deletion ocaml-lsp-server/src/check_for_comments.mli
Original file line number Diff line number Diff line change
@@ -1,2 +1,3 @@
(** Returns [true] if [position] occurs inside a comment in the document *)
val position_in_comment : position:Position.t -> merlin:Document.Merlin.t -> bool Fiber.t
val position_in_comment :
position:Position.t -> merlin:Document.Merlin.t -> bool Fiber.t
46 changes: 27 additions & 19 deletions ocaml-lsp-server/src/compl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -242,12 +242,13 @@ module Complete_with_construct = struct
end

let complete (state : State.t)
({ textDocument = { uri }; position = pos; context; _ } : CompletionParams.t) =
({ textDocument = { uri }; position = pos; context; _ } :
CompletionParams.t) =
Fiber.of_thunk (fun () ->
let doc = Document_store.get state.store uri in
match Document.kind doc with
| `Other -> Fiber.return None
| `Merlin merlin ->
| `Merlin merlin -> (
let completion_item_capability =
let open Option.O in
let capabilities = State.client_capabilities state in
Expand All @@ -267,26 +268,29 @@ let complete (state : State.t)
in
let* should_provide_completions =
match context with
| Some context ->
(match context.triggerKind with
| TriggerCharacter ->
let+ inside_comment =
Check_for_comments.position_in_comment ~position:pos ~merlin
in
(match inside_comment with
| true -> `Ignore
| false -> `Provide_completions)
| Invoked | TriggerForIncompleteCompletions ->
Fiber.return `Provide_completions)
| Some context -> (
match context.triggerKind with
| TriggerCharacter -> (
let+ inside_comment =
Check_for_comments.position_in_comment ~position:pos ~merlin
in
match inside_comment with
| true -> `Ignore
| false -> `Provide_completions)
| Invoked | TriggerForIncompleteCompletions ->
Fiber.return `Provide_completions)
| None -> Fiber.return `Provide_completions
in
(match should_provide_completions with
| `Ignore -> Fiber.return None
| `Provide_completions ->
match should_provide_completions with
| `Ignore -> Fiber.return None
| `Provide_completions ->
let+ items =
let position = Position.logical pos in
let prefix =
prefix_of_position ~short_path:false (Document.source doc) position
prefix_of_position
~short_path:false
(Document.source doc)
position
in
let deprecated =
Option.value
Expand All @@ -299,7 +303,9 @@ let complete (state : State.t)
Complete_by_prefix.complete merlin prefix pos ~resolve ~deprecated
else
let reindex_sortText completion_items =
List.mapi completion_items ~f:(fun idx (ci : CompletionItem.t) ->
List.mapi
completion_items
~f:(fun idx (ci : CompletionItem.t) ->
let sortText = Some (sortText_of_index idx) in
{ ci with sortText })
in
Expand Down Expand Up @@ -349,7 +355,9 @@ let complete (state : State.t)
construct_completionItems @ compl_by_prefix_completionItems
|> reindex_sortText |> preselect_first
in
Some (`CompletionList (CompletionList.create ~isIncomplete:false ~items ()))))
Some
(`CompletionList
(CompletionList.create ~isIncomplete:false ~items ()))))

let format_doc ~markdown doc =
match markdown with
Expand Down
1 change: 1 addition & 0 deletions ocaml-lsp-server/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ module Asttypes = Ocaml_parsing.Asttypes
module Cmt_format = Ocaml_typing.Cmt_format
module Ident = Ocaml_typing.Ident
module Env = Ocaml_typing.Env
module Merlin_parsing = Ocaml_parsing

module Loc = struct
module T = struct
Expand Down
4 changes: 3 additions & 1 deletion ocaml-lsp-server/src/signature_help.ml
Original file line number Diff line number Diff line change
Expand Up @@ -197,7 +197,9 @@ let run (state : State.t)
Fiber.return help
| `Merlin merlin -> (
let* application_signature =
let* inside_comment = Check_for_comments.position_in_comment ~position ~merlin in
let* inside_comment =
Check_for_comments.position_in_comment ~position ~merlin
in
match inside_comment with
| true -> Fiber.return None
| false ->
Expand Down

0 comments on commit a05af8f

Please sign in to comment.