File tree Expand file tree Collapse file tree 4 files changed +30
-13
lines changed Expand file tree Collapse file tree 4 files changed +30
-13
lines changed Original file line number Diff line number Diff line change @@ -54,12 +54,10 @@ let compute_ocaml_code_actions (params : CodeActionParams.t) state doc =
54
54
]
55
55
in
56
56
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)
63
61
in
64
62
let * batch_results =
65
63
if List. is_empty batchable
Original file line number Diff line number Diff line change @@ -37,13 +37,34 @@ include struct
37
37
end
38
38
39
39
module List = struct
40
- include Stdune. List
41
- open Base.List
40
+ include Base. List
42
41
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
43
56
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
44
64
let find_mapi xs ~f = find_mapi xs ~f
45
65
let sub xs ~pos ~len = sub xs ~pos ~len
46
66
let hd_exn t = hd_exn t
67
+ let hd_opt t = hd t
47
68
let nth_exn t n = nth_exn t n
48
69
let hd t = hd t
49
70
let filter t ~f = filter t ~f
Original file line number Diff line number Diff line change @@ -527,6 +527,7 @@ let on_request
527
527
match req with
528
528
| Client_request. UnknownRequest { meth; params } ->
529
529
(match
530
+ List. assoc
530
531
[ ( Req_switch_impl_intf. meth
531
532
, fun ~params state ->
532
533
Fiber. of_thunk (fun () ->
@@ -545,8 +546,7 @@ let on_request
545
546
, Semantic_highlighting.Debug. on_request_full )
546
547
; ( Req_hover_extended. meth
547
548
, fun ~params _ -> Req_hover_extended. on_request ~params rpc )
548
- ]
549
- |> List. assoc_opt meth
549
+ ] meth
550
550
with
551
551
| None ->
552
552
Jsonrpc.Response.Error. raise
Original file line number Diff line number Diff line change @@ -368,9 +368,7 @@ let run server (state : State.t) (params : WorkspaceSymbolParams.t) =
368
368
| Error `Cancelled -> assert false
369
369
| Error (`Exn exn ) -> Exn_with_backtrace. reraise exn )
370
370
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
374
372
in
375
373
let + () =
376
374
match errors with
You can’t perform that action at this time.
0 commit comments