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 =
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
Original file line number Diff line number Diff line change @@ -61,13 +61,34 @@ include struct
6161end
6262
6363module List = struct
64- include Stdune. List
65- open Base.List
64+ include Base. List
6665
66+ let compare xs ys ~compare =
67+ Base.List. compare (fun x y -> Ordering. to_int (compare x y)) xs ys
68+ ;;
69+
70+ let sort xs ~compare = sort xs ~compare: (fun x y -> Ordering. to_int (compare x y))
71+ let fold_left2 xs ys ~init ~f = Stdlib.List. fold_left2 f init xs ys
72+ let assoc xs key = Assoc. find ~equal: Poly. equal xs key
73+ let assoc_opt xs key = assoc xs key
74+ let mem t x ~equal = mem t x ~equal
75+ let map t ~f = map t ~f
76+ let concat_map t ~f = concat_map t ~f
77+ let flatten t = Stdlib.List. flatten t
78+ let filter_map t ~f = filter_map t ~f
79+ let fold_left t ~init ~f = fold_left t ~init ~f
6780 let findi xs ~f = findi xs ~f
81+ let find_opt xs ~f = find xs ~f
82+
83+ let sort_uniq xs ~compare =
84+ Stdlib.List. sort_uniq (fun x y -> Ordering. to_int (compare x y)) xs
85+ ;;
86+
87+ let for_all xs ~f = for_all xs ~f
6888 let find_mapi xs ~f = find_mapi xs ~f
6989 let sub xs ~pos ~len = sub xs ~pos ~len
7090 let hd_exn t = hd_exn t
91+ let hd_opt t = hd t
7192 let nth_exn t n = nth_exn t n
7293 let hd t = hd t
7394 let filter t ~f = filter t ~f
Original file line number Diff line number Diff line change @@ -535,6 +535,7 @@ let on_request
535535 match req with
536536 | Client_request. UnknownRequest { meth; params } ->
537537 (match
538+ List. assoc
538539 [ ( Req_switch_impl_intf. meth
539540 , fun ~params state ->
540541 Fiber. of_thunk (fun () ->
@@ -553,8 +554,7 @@ let on_request
553554 , Semantic_highlighting.Debug. on_request_full )
554555 ; ( Req_hover_extended. meth
555556 , fun ~params _ -> Req_hover_extended. on_request ~params rpc )
556- ]
557- |> List. assoc_opt meth
557+ ] meth
558558 with
559559 | None ->
560560 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) =
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
You can’t perform that action at this time.
0 commit comments