Skip to content

Commit c641cc3

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 b203fb4 commit c641cc3

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
@@ -53,12 +53,10 @@ let compute_ocaml_code_actions (params : CodeActionParams.t) state doc =
5353
]
5454
in
5555
let batchable, non_batchable =
56-
List.partition_map
57-
~f:(fun ca ->
58-
match ca.run with
59-
| `Batchable f -> Left f
60-
| `Non_batchable f -> Right f)
61-
enabled_actions
56+
List.partition_map enabled_actions ~f:(fun ca ->
57+
match ca.run with
58+
| `Batchable f -> Base.Either.First f
59+
| `Non_batchable f -> Second f)
6260
in
6361
let* batch_results =
6462
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
@@ -38,13 +38,34 @@ include struct
3838
end
3939

4040
module List = struct
41-
include Stdune.List
42-
open Base.List
41+
include Base.List
4342

43+
let compare xs ys ~compare =
44+
Base.List.compare (fun x y -> Ordering.to_int (compare x y)) xs ys
45+
;;
46+
47+
let sort xs ~compare = sort xs ~compare:(fun x y -> Ordering.to_int (compare x y))
48+
let fold_left2 xs ys ~init ~f = Stdlib.List.fold_left2 f init xs ys
49+
let assoc xs key = Assoc.find ~equal:Poly.equal xs key
50+
let assoc_opt xs key = assoc xs key
51+
let mem t x ~equal = mem t x ~equal
52+
let map t ~f = map t ~f
53+
let concat_map t ~f = concat_map t ~f
54+
let flatten t = Stdlib.List.flatten t
55+
let filter_map t ~f = filter_map t ~f
56+
let fold_left t ~init ~f = fold_left t ~init ~f
4457
let findi xs ~f = findi xs ~f
58+
let find_opt xs ~f = find xs ~f
59+
60+
let sort_uniq xs ~compare =
61+
Stdlib.List.sort_uniq (fun x y -> Ordering.to_int (compare x y)) xs
62+
;;
63+
64+
let for_all xs ~f = for_all xs ~f
4565
let find_mapi xs ~f = find_mapi xs ~f
4666
let sub xs ~pos ~len = sub xs ~pos ~len
4767
let hd_exn t = hd_exn t
68+
let hd_opt t = hd t
4869
let nth_exn t n = nth_exn t n
4970
let hd t = hd t
5071
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
@@ -519,6 +519,7 @@ let on_request
519519
match req with
520520
| Client_request.UnknownRequest { meth; params } ->
521521
(match
522+
List.assoc
522523
[ ( Req_switch_impl_intf.meth
523524
, fun ~params state ->
524525
Fiber.of_thunk (fun () ->
@@ -536,8 +537,7 @@ let on_request
536537
, Semantic_highlighting.Debug.on_request_full )
537538
; ( Req_hover_extended.meth
538539
, fun ~params _ -> Req_hover_extended.on_request ~params rpc )
539-
]
540-
|> List.assoc_opt meth
540+
] meth
541541
with
542542
| None ->
543543
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
@@ -364,9 +364,7 @@ let run server (state : State.t) (params : WorkspaceSymbolParams.t) =
364364
| Error `Cancelled -> assert false
365365
| Error (`Exn exn) -> Exn_with_backtrace.reraise exn)
366366
in
367-
List.partition_map symbols_results ~f:(function
368-
| Ok r -> Left r
369-
| Error e -> Right e)
367+
List.partition_result symbols_results
370368
in
371369
let+ () =
372370
match errors with

0 commit comments

Comments
 (0)