Skip to content

Commit

Permalink
cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
jchavarri committed Apr 17, 2024
1 parent 05cc0f4 commit 444095b
Show file tree
Hide file tree
Showing 11 changed files with 7 additions and 253 deletions.
4 changes: 2 additions & 2 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,8 @@

- Support folding of `ifthenelse` expressions (#1031)

- Add `getDuneContexts` method and spawn a new `ocaml-merlin` process per
Dune context (#1238)
- Add `getDuneContexts` method, `--context` flag, and spawn a new `ocaml-merlin`
process per Dune context (#1238)

## Fixes

Expand Down
7 changes: 0 additions & 7 deletions ocaml-lsp-server/docs/ocamllsp/config.md
Original file line number Diff line number Diff line change
Expand Up @@ -35,12 +35,5 @@ interface config {
* @since 1.18
*/
inlayHints: { enable : boolean }

/**
* Set the current Dune context for Merlin
* @default "default"
* @since 1.18
*/
duneContext: { value : string }
}
```
131 changes: 2 additions & 129 deletions ocaml-lsp-server/src/config_data.ml
Original file line number Diff line number Diff line change
Expand Up @@ -315,101 +315,6 @@ module DuneDiagnostics = struct
[@@@end]
end

module DuneContext = struct
type selected =
| Default
| Custom of string

type t = { value : selected [@default Default] }
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]

let to_string = function
| Default -> "default"
| Custom str -> str

let of_string = function
| "default" -> Default
| str -> Custom str

let to_dyn t = Dyn.string (to_string t)

let equal a b =
match (a, b) with
| Default, Default -> true
| Custom str1, Custom str2 when String.equal str1 str2 -> true
| Default, Custom _ | Custom _, Default | Custom _, Custom _ -> false

let t_of_yojson =
(let _tp_loc = "ocaml-lsp-server/src/config_data.ml.DuneContext.t" in
function
| `Assoc field_yojsons as yojson -> (
let value_field = ref Ppx_yojson_conv_lib.Option.None
and duplicates = ref []
and extra = ref [] in
let rec iter = function
| (field_name, _field_yojson) :: tail ->
(match field_name with
| "value" -> (
match Ppx_yojson_conv_lib.( ! ) value_field with
| Ppx_yojson_conv_lib.Option.None ->
let fvalue = string_of_yojson _field_yojson in
value_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| _ -> ());
iter tail
| [] -> ()
in
iter field_yojsons;
match Ppx_yojson_conv_lib.( ! ) duplicates with
| _ :: _ ->
Ppx_yojson_conv_lib.Yojson_conv_error.record_duplicate_fields
_tp_loc
(Ppx_yojson_conv_lib.( ! ) duplicates)
yojson
| [] -> (
match Ppx_yojson_conv_lib.( ! ) extra with
| _ :: _ ->
Ppx_yojson_conv_lib.Yojson_conv_error.record_extra_fields
_tp_loc
(Ppx_yojson_conv_lib.( ! ) extra)
yojson
| [] ->
let value_value = Ppx_yojson_conv_lib.( ! ) value_field in
{ value =
(match value_value with
| Ppx_yojson_conv_lib.Option.None
| Ppx_yojson_conv_lib.Option.Some "default" -> Default
| Ppx_yojson_conv_lib.Option.Some v -> Custom v)
}))
| _ as yojson ->
Ppx_yojson_conv_lib.Yojson_conv_error.record_list_instead_atom
_tp_loc
yojson
: Ppx_yojson_conv_lib.Yojson.Safe.t -> t)

let _ = t_of_yojson

let yojson_of_t =
(function
| { value = v_value } ->
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
let bnds =
let arg =
match v_value with
| Default -> "default"
| Custom ctxt -> ctxt
in
("value", yojson_of_string arg) :: bnds
in
`Assoc bnds
: t -> Ppx_yojson_conv_lib.Yojson.Safe.t)

let _ = yojson_of_t

[@@@end]
end

type t =
{ codelens : Lens.t Json.Nullable_option.t
[@default None] [@yojson_drop_default ( = )]
Expand All @@ -419,8 +324,6 @@ type t =
[@key "inlayHints"] [@default None] [@yojson_drop_default ( = )]
; dune_diagnostics : DuneDiagnostics.t Json.Nullable_option.t
[@key "duneDiagnostics"] [@default None] [@yojson_drop_default ( = )]
; dune_context : DuneContext.t Json.Nullable_option.t
[@key "duneContext"] [@default None] [@yojson_drop_default ( = )]
}
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]

Expand All @@ -434,7 +337,6 @@ let t_of_yojson =
and extended_hover_field = ref Ppx_yojson_conv_lib.Option.None
and inlay_hints_field = ref Ppx_yojson_conv_lib.Option.None
and dune_diagnostics_field = ref Ppx_yojson_conv_lib.Option.None
and dune_context_field = ref Ppx_yojson_conv_lib.Option.None
and duplicates = ref []
and extra = ref [] in
let rec iter = function
Expand Down Expand Up @@ -482,17 +384,6 @@ let t_of_yojson =
dune_diagnostics_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| "duneContext" -> (
match Ppx_yojson_conv_lib.( ! ) dune_context_field with
| Ppx_yojson_conv_lib.Option.None ->
let fvalue =
Json.Nullable_option.t_of_yojson
DuneContext.t_of_yojson
_field_yojson
in
dune_context_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| _ -> ());
iter tail
| [] -> ()
Expand All @@ -515,13 +406,11 @@ let t_of_yojson =
let ( codelens_value
, extended_hover_value
, inlay_hints_value
, dune_diagnostics_value
, dune_context_value ) =
, dune_diagnostics_value ) =
( Ppx_yojson_conv_lib.( ! ) codelens_field
, Ppx_yojson_conv_lib.( ! ) extended_hover_field
, Ppx_yojson_conv_lib.( ! ) inlay_hints_field
, Ppx_yojson_conv_lib.( ! ) dune_diagnostics_field
, Ppx_yojson_conv_lib.( ! ) dune_context_field )
, Ppx_yojson_conv_lib.( ! ) dune_diagnostics_field )
in
{ codelens =
(match codelens_value with
Expand All @@ -539,10 +428,6 @@ let t_of_yojson =
(match dune_diagnostics_value with
| Ppx_yojson_conv_lib.Option.None -> None
| Ppx_yojson_conv_lib.Option.Some v -> v)
; dune_context =
(match dune_context_value with
| Ppx_yojson_conv_lib.Option.None -> None
| Ppx_yojson_conv_lib.Option.Some v -> v)
}))
| _ as yojson ->
Ppx_yojson_conv_lib.Yojson_conv_error.record_list_instead_atom
Expand All @@ -558,7 +443,6 @@ let yojson_of_t =
; extended_hover = v_extended_hover
; inlay_hints = v_inlay_hints
; dune_diagnostics = v_dune_diagnostics
; dune_context = v_dune_context
} ->
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
let bnds =
Expand Down Expand Up @@ -600,16 +484,6 @@ let yojson_of_t =
let bnd = ("codelens", arg) in
bnd :: bnds
in
let bnds =
if None = v_dune_context then bnds
else
let arg =
(Json.Nullable_option.yojson_of_t DuneContext.yojson_of_t)
v_dune_context
in
let bnd = ("duneContext", arg) in
bnd :: bnds
in
`Assoc bnds
: t -> Ppx_yojson_conv_lib.Yojson.Safe.t)

Expand All @@ -623,5 +497,4 @@ let default =
; inlay_hints =
Some { hint_pattern_variables = false; hint_let_bindings = false }
; dune_diagnostics = Some { enable = true }
; dune_context = Some { value = Default }
}
5 changes: 0 additions & 5 deletions ocaml-lsp-server/src/configuration.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,3 @@ let report_dune_diagnostics t =
match t.data.dune_diagnostics with
| Some { enable = true } | None -> true
| Some { enable = false } -> false

let dune_context t =
match t.data.dune_context with
| Some { value = v } -> v
| None -> Default
2 changes: 0 additions & 2 deletions ocaml-lsp-server/src/configuration.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,5 +12,3 @@ val wheel : t -> Lev_fiber.Timer.Wheel.t
val update : t -> DidChangeConfigurationParams.t -> t Fiber.t

val report_dune_diagnostics : t -> bool

val dune_context : t -> Config_data.DuneContext.selected
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/merlin_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -202,7 +202,7 @@ module Process = struct
; "ocaml-merlin"
; "--no-print-directory"
; "--context"
; Config_data.DuneContext.to_string dune_context
; dune_context
]
in
Pid.of_int
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/merlin_config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ type t

val should_read_dot_merlin : bool ref

val dune_context : Config_data.DuneContext.selected option ref
val dune_context : string option ref

val config : t -> Mconfig.t Fiber.t

Expand Down
7 changes: 1 addition & 6 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -723,10 +723,6 @@ let on_notification server (notification : Client_notification.t) :
~report_dune_diagnostics
(State.diagnostics state)
in
let state =
let dune_context = Configuration.dune_context configuration in
State.set_dune_context state ~dune_context
in
{ state with configuration }
| DidSaveTextDocument { textDocument = { uri }; _ } -> (
let state = Server.state server in
Expand Down Expand Up @@ -944,8 +940,7 @@ let run channel ~dune_context ~read_dot_merlin () =
Merlin_utils.Lib_config.set_program_name "ocamllsp";
Merlin_utils.Lib_config.System.set_run_in_directory (run_in_directory ());
Merlin_config.should_read_dot_merlin := read_dot_merlin;
Merlin_config.dune_context :=
Option.map dune_context ~f:Config_data.DuneContext.of_string;
Merlin_config.dune_context := Option.map dune_context ~f:Fun.id;
Unix.putenv "__MERLIN_MASTER_PID" (string_of_int (Unix.getpid ()));
Lev_fiber.run ~sigpipe:`Ignore (fun () ->
let* input, output = stream_of_channel channel in
Expand Down
7 changes: 0 additions & 7 deletions ocaml-lsp-server/src/state.ml
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,6 @@ type t =
; symbols_thread : Lev_fiber.Thread.t Lazy_fiber.t
; wheel : Lev_fiber.Timer.Wheel.t
; hover_extended : hover_extended
; selected_context : Config_data.DuneContext.selected
}

let create ~store ~merlin ~detached ~configuration ~ocamlformat_rpc
Expand All @@ -41,11 +40,8 @@ let create ~store ~merlin ~detached ~configuration ~ocamlformat_rpc
; symbols_thread
; wheel
; hover_extended = { history = None }
; selected_context = Default
}

let dune_context t = t.selected_context

let wheel t = t.wheel

let initialize_params (state : t) =
Expand Down Expand Up @@ -107,9 +103,6 @@ let modify_workspaces t ~f =
in
{ t with init }

let set_dune_context (t : t) ~dune_context =
{ t with selected_context = dune_context }

let client_capabilities t = (initialize_params t).capabilities

let experimental_client_capabilities t =
Expand Down
5 changes: 0 additions & 5 deletions ocaml-lsp-server/src/state.mli
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@ type t =
; symbols_thread : Lev_fiber.Thread.t Lazy_fiber.t
; wheel : Lev_fiber.Timer.Wheel.t
; hover_extended : hover_extended
; selected_context : Config_data.DuneContext.selected
}

val create :
Expand Down Expand Up @@ -67,10 +66,6 @@ val dune : t -> Dune.t

val modify_workspaces : t -> f:(Workspaces.t -> Workspaces.t) -> t

val dune_context : t -> Config_data.DuneContext.selected

val set_dune_context : t -> dune_context:Config_data.DuneContext.selected -> t

(** @return
client capabilities passed from the client in [InitializeParams]; use
[exp_client_caps] to get {i experimental} client capabilities.
Expand Down
Loading

0 comments on commit 444095b

Please sign in to comment.