Skip to content

Commit

Permalink
Add <> to comparable ops and add such ops to Bool
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Mar 14, 2019
1 parent 2ab20c2 commit 6998a4c
Show file tree
Hide file tree
Showing 4 changed files with 10 additions and 2 deletions.
7 changes: 5 additions & 2 deletions src/stdune/bool.ml
Original file line number Diff line number Diff line change
@@ -1,12 +1,15 @@
type t = bool

let compare x y =
match x, y with
| true, true
| false, false -> Ordering.Eq
| true, false -> Gt
| false, true -> Lt

include Comparable.Operators(struct
type nonrec t = bool
let compare = compare
end)

let to_string = string_of_bool

let of_string s = Option.try_with (fun () -> bool_of_string s)
2 changes: 2 additions & 0 deletions src/stdune/bool.mli
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@ type t = bool

val compare : t -> t -> Ordering.t

include Comparable.OPS with type t := t

val to_string : t -> string

val of_string : string -> t option
2 changes: 2 additions & 0 deletions src/stdune/comparable.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module type OPS = sig
val (>) : t -> t -> bool
val (<=) : t -> t -> bool
val (<) : t -> t -> bool
val (<>) : t -> t -> bool
end

module Operators (X : S) = struct
Expand All @@ -22,6 +23,7 @@ module Operators (X : S) = struct
| Gt | Lt -> false

let equal = (=)
let (<>) a b = not (a = b)

let (>=) a b =
match X.compare a b with
Expand Down
1 change: 1 addition & 0 deletions src/stdune/comparable.mli
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module type OPS = sig
val (>) : t -> t -> bool
val (<=) : t -> t -> bool
val (<) : t -> t -> bool
val (<>) : t -> t -> bool
end

module Operators (X : S) : OPS with type t = X.t

0 comments on commit 6998a4c

Please sign in to comment.