Skip to content

Commit

Permalink
Add and export relop related utils
Browse files Browse the repository at this point in the history
Signed-off-by: Mathieu Barbin <[email protected]>
  • Loading branch information
mbarbin committed Sep 30, 2024
1 parent 7130814 commit 0af14e0
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 0 deletions.
2 changes: 2 additions & 0 deletions src/format/opamFormula.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,8 @@

type relop = [`Eq|`Neq|`Geq|`Gt|`Leq|`Lt]

let all_relop = [ `Eq ; `Neq ; `Geq ; `Gt ; `Leq ; `Lt ]

let neg_relop = function
| `Eq -> `Neq
| `Neq -> `Eq
Expand Down
7 changes: 7 additions & 0 deletions src/format/opamFormula.mli
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,13 @@ type relop = OpamParserTypes.FullPos.relop_kind (* = [ `Eq | `Neq | `Geq | `Gt |

val compare_relop : relop -> relop -> int

(** A list containing each available operator once. *)
val all_relop : relop list

(** Returns a string representing the operator in infix syntax, as
used in opam files (">", "=", etc.) *)
val string_of_relop : relop -> string

(** Version constraints for OPAM *)
type version_constraint = relop * OpamPackage.Version.t

Expand Down

0 comments on commit 0af14e0

Please sign in to comment.