Skip to content

Commit

Permalink
refactor: remove more stdune cruft
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

<!-- ps-id: 66324ec5-3557-4523-9d4a-6f6906e633a8 -->

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Feb 23, 2025
1 parent b203fb4 commit 40b84f1
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 9 deletions.
12 changes: 8 additions & 4 deletions ocaml-lsp-server/src/import.ml
Original file line number Diff line number Diff line change
@@ -1,22 +1,26 @@
(* All modules from [Stdune] should be in the struct below. The modules are
listed alphabetically. Try to keep the order. *)

module Poly = struct
let equal = ( = )
let compare x y = Ordering.of_int (compare x y)
let hash x = Hashtbl.hash x
end

let sprintf = Printf.sprintf

include struct
open Stdune
module Code_error = Code_error
module Comparable = Comparable
module Exn_with_backtrace = Exn_with_backtrace
module Int = Int
module Table = Table
module Tuple = Tuple
module Unix_env = Env
module Io = Io
module Map = Map
module Monoid = Monoid
module Pid = Pid
module Poly = Poly

let sprintf = sprintf
end

include struct
Expand Down
5 changes: 1 addition & 4 deletions ocaml-lsp-server/src/position.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,10 +37,7 @@ let ( - ) ({ line; character } : t) (t : t) : t =
;;

let abs ({ line; character } : t) : t = { line = abs line; character = abs character }

let compare ({ line; character } : t) (t : t) : Ordering.t =
Stdune.Tuple.T2.compare Int.compare Int.compare (line, character) (t.line, t.character)
;;
let compare (x : t) (t : t) : Ordering.t = Poly.compare x t

let compare_inclusion (t : t) (r : Lsp.Types.Range.t) =
match compare t r.start, compare t r.end_ with
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/range.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ let contains (x : t) (y : t) =
let compare_size (x : t) (y : t) =
let dx = Position.(x.end_ - x.start) in
let dy = Position.(y.end_ - y.start) in
Tuple.T2.compare Int.compare Int.compare (dx.line, dy.line) (dx.character, dy.character)
Poly.compare (dx.line, dy.line) (dx.character, dy.character)
;;

let first_line =
Expand Down

0 comments on commit 40b84f1

Please sign in to comment.