/usr/lib/ocaml/oasis/OASISVersion.mli is in liboasis-ocaml-dev 0.3.0-4.
This file is owned by root:root, with mode 0o644.
The actual contents of the file can be viewed below.
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 | (******************************************************************************)
(* OASIS: architecture for building OCaml libraries and applications *)
(* *)
(* Copyright (C) 2008-2010, OCamlCore SARL *)
(* *)
(* This library is free software; you can redistribute it and/or modify it *)
(* under the terms of the GNU Lesser General Public License as published by *)
(* the Free Software Foundation; either version 2.1 of the License, or (at *)
(* your option) any later version, with the OCaml static compilation *)
(* exception. *)
(* *)
(* This library is distributed in the hope that it will be useful, but *)
(* WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *)
(* or FITNESS FOR A PARTICULAR PURPOSE. See the file COPYING for more *)
(* details. *)
(* *)
(* You should have received a copy of the GNU Lesser General Public License *)
(* along with this library; if not, write to the Free Software Foundation, *)
(* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA *)
(******************************************************************************)
(** Version comparisons
This module handles versions and version comparators. A version is a string
of the form "1.0.0". We compare integer and non-integer parts between to
version to order them. Version comparators defined relations to a set
of version. E.g. ">= 1.0.0" is a version comparator and defines all version
above "1.0.0", including "1.0.0".
The version comparison is done using Debian policy for version:
http://www.debian.org/doc/debian-policy/ch-controlfields.html#s-f-Version
@author Sylvain Le Gall
*)
(** {2 Version} *)
type s = string
type t
(** Compare versions.
*)
val version_compare: t -> t -> int
(** Convert a string to version.
*)
val version_of_string: string -> t
(** Convert a version to string.
*)
val string_of_version: t -> string
(** Version number value. {b Not exported}.
*)
val value: t OASISValues.t
(** Dump [ODN.t]. {b Not exported}.
*)
val odn_of_t: t -> ODN.t
(** Remove the last part of a version, after the last '.'. I.e. 0.2.0~alpha1 ->
0.2.
*)
val chop: t -> t
(** {2 Version comparator} *)
type comparator =
| VGreater of t
| VGreaterEqual of t
| VEqual of t
| VLesser of t
| VLesserEqual of t
| VOr of comparator * comparator
| VAnd of comparator * comparator
(** Apply version comparator expression.
*)
val comparator_apply: t -> comparator -> bool
(** Convert a comparator to string.
*)
val string_of_comparator: comparator -> string
(** Convert a comparator to variable name.
*)
val varname_of_comparator: comparator -> string
(** Convert a string to comparator. {b Not exported}.
*)
val comparator_of_string: string -> comparator
(** Simplify comparator, if possible. {b Not exported}.
*)
val comparator_reduce: comparator -> comparator
(** Check that we have a version constraint. {b Not exported}.
*)
val comparator_value: comparator OASISValues.t
(** Check that >= 0.3, useful for oasis version comparison.
*)
val version_0_3_or_after : t -> bool
(** Dump [ODN.t]. {b Not exported}.
*)
val odn_of_comparator: comparator -> ODN.t
|