Skip to content

Commit

Permalink
Add active_param
Browse files Browse the repository at this point in the history
  • Loading branch information
3Rafal committed Jan 5, 2024
1 parent 77a4878 commit 3a4aee2
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 3 deletions.
5 changes: 3 additions & 2 deletions src/frontend/ocamlmerlin/query_json.ml
Original file line number Diff line number Diff line change
Expand Up @@ -356,11 +356,12 @@ let json_of_signature_help resp =
`Assoc [ "label_start", `Int label_start; "label_end", `Int label_end] in
match resp with
| None -> `Assoc []
| Some { function_name; signature; parameters } ->
| Some { function_name; signature; parameters; active_param } ->
`Assoc
[ "function_name", `String (Option.value ~default:"_" function_name);
"signature", `String signature;
"parameters", `List (List.map ~f:param parameters)
"parameters", `List (List.map ~f:param parameters);
"active_param", `Int active_param
]

let json_of_response (type a) (query : a t) (response : a) : json =
Expand Down
1 change: 1 addition & 0 deletions src/frontend/query_commands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -858,6 +858,7 @@ let dispatch pipeline (type a) : a Query_protocol.t -> a =
Some { function_name = s.function_name;
signature = s.signature;
parameters = List.map ~f:(param (String.length prefix)) s.parameters;
active_param = Option.value ~default:0 s.active_param;
}
| None -> None)

Expand Down
1 change: 1 addition & 0 deletions src/frontend/query_protocol.ml
Original file line number Diff line number Diff line change
Expand Up @@ -105,6 +105,7 @@ type signature_help = {
function_name : string option;
signature : string;
parameters : signature_help_param list;
active_param : int
}

type is_tail_position = [`No | `Tail_position | `Tail_call]
Expand Down
3 changes: 2 additions & 1 deletion tests/test-dirs/signature-help.t
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,8 @@ It can provide signature help after a function-type value
"label_start": 22,
"label_end": 29
}
]
],
"active_param": 1
},
"notifications": []
}

0 comments on commit 3a4aee2

Please sign in to comment.