Skip to content

Commit 9beb3e2

Browse files
committed
refactor: remove uses of [Stdune.List]
Signed-off-by: Rudi Grinberg <[email protected]> <!-- ps-id: 8cf5536e-698b-4c53-90ce-114d68a8f87a --> Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 5b6fd4b commit 9beb3e2

File tree

4 files changed

+30
-13
lines changed

4 files changed

+30
-13
lines changed

ocaml-lsp-server/src/code_actions.ml

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -54,12 +54,10 @@ let compute_ocaml_code_actions (params : CodeActionParams.t) state doc =
5454
]
5555
in
5656
let batchable, non_batchable =
57-
List.partition_map
58-
~f:(fun ca ->
59-
match ca.run with
60-
| `Batchable f -> Left f
61-
| `Non_batchable f -> Right f)
62-
enabled_actions
57+
List.partition_map enabled_actions ~f:(fun ca ->
58+
match ca.run with
59+
| `Batchable f -> Base.Either.First f
60+
| `Non_batchable f -> Second f)
6361
in
6462
let* batch_results =
6563
if List.is_empty batchable

ocaml-lsp-server/src/import.ml

Lines changed: 23 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -37,13 +37,34 @@ include struct
3737
end
3838

3939
module List = struct
40-
include Stdune.List
41-
open Base.List
40+
include Base.List
4241

42+
let compare xs ys ~compare =
43+
Base.List.compare (fun x y -> Ordering.to_int (compare x y)) xs ys
44+
;;
45+
46+
let sort xs ~compare = sort xs ~compare:(fun x y -> Ordering.to_int (compare x y))
47+
let fold_left2 xs ys ~init ~f = Stdlib.List.fold_left2 f init xs ys
48+
let assoc xs key = Assoc.find ~equal:Poly.equal xs key
49+
let assoc_opt xs key = assoc xs key
50+
let mem t x ~equal = mem t x ~equal
51+
let map t ~f = map t ~f
52+
let concat_map t ~f = concat_map t ~f
53+
let flatten t = Stdlib.List.flatten t
54+
let filter_map t ~f = filter_map t ~f
55+
let fold_left t ~init ~f = fold_left t ~init ~f
4356
let findi xs ~f = findi xs ~f
57+
let find_opt xs ~f = find xs ~f
58+
59+
let sort_uniq xs ~compare =
60+
Stdlib.List.sort_uniq (fun x y -> Ordering.to_int (compare x y)) xs
61+
;;
62+
63+
let for_all xs ~f = for_all xs ~f
4464
let find_mapi xs ~f = find_mapi xs ~f
4565
let sub xs ~pos ~len = sub xs ~pos ~len
4666
let hd_exn t = hd_exn t
67+
let hd_opt t = hd t
4768
let nth_exn t n = nth_exn t n
4869
let hd t = hd t
4970
let filter t ~f = filter t ~f

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -527,6 +527,7 @@ let on_request
527527
match req with
528528
| Client_request.UnknownRequest { meth; params } ->
529529
(match
530+
List.assoc
530531
[ ( Req_switch_impl_intf.meth
531532
, fun ~params state ->
532533
Fiber.of_thunk (fun () ->
@@ -545,8 +546,7 @@ let on_request
545546
, Semantic_highlighting.Debug.on_request_full )
546547
; ( Req_hover_extended.meth
547548
, fun ~params _ -> Req_hover_extended.on_request ~params rpc )
548-
]
549-
|> List.assoc_opt meth
549+
] meth
550550
with
551551
| None ->
552552
Jsonrpc.Response.Error.raise

ocaml-lsp-server/src/workspace_symbol.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -368,9 +368,7 @@ let run server (state : State.t) (params : WorkspaceSymbolParams.t) =
368368
| Error `Cancelled -> assert false
369369
| Error (`Exn exn) -> Exn_with_backtrace.reraise exn)
370370
in
371-
List.partition_map symbols_results ~f:(function
372-
| Ok r -> Left r
373-
| Error e -> Right e)
371+
List.partition_result symbols_results
374372
in
375373
let+ () =
376374
match errors with

0 commit comments

Comments
 (0)