-
Notifications
You must be signed in to change notification settings - Fork 373
/
Copy pathopamCLIVersion.ml
87 lines (69 loc) · 2.73 KB
/
opamCLIVersion.ml
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
(**************************************************************************)
(* *)
(* Copyright 2020 David Allsopp Ltd. *)
(* *)
(* All rights reserved. This file is distributed under the terms of the *)
(* GNU Lesser General Public License version 2.1, with the special *)
(* exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
type t = int * int
let supported_versions = [(2, 0); (2, 1); (2,2); (2,3); (2,4)]
let is_supported v = List.mem v supported_versions
let of_string s =
match String.index s '.' with
| i when s.[0] <> '0' && (i >= String.length s - 2 || s.[i + 1] <> '0') ->
begin
try Scanf.sscanf s "%u.%u%!" (fun major minor -> (major, minor))
with Scanf.Scan_failure _ ->
Printf.ksprintf failwith "OpamVersion.CLI.of_string: %s" s
end
| exception Not_found ->
Printf.ksprintf failwith "OpamVersion.CLI.of_string: %s" s
| _ -> Printf.ksprintf failwith "OpamVersion.CLI.of_string: %s" s
let current = of_string @@ OpamVersion.(to_string current_nopatch)
(* This line is checked on CI to ensure that default cli version
matches release opam version *)
let default = (2,0)
let of_string_opt s = try Some (of_string s) with Failure _ -> None
let to_string (major, minor) = Printf.sprintf "%d.%d" major minor
let to_json v = `String (to_string v)
let of_json = function
| `String x -> of_string_opt x
| _ -> None
let ( >= ) = Stdlib.( >= )
let ( < ) = Stdlib.( < )
let compare (vm, vn) (wm, wn) =
let major = Int.compare vm wm in
if major <> 0 then major else
Int.compare vn wn
let equal v w = compare v w = 0
let previous cli =
let f previous version =
if version > previous && cli > version then version else previous
in
let zero = (0, 0) in
let previous = List.fold_left f zero supported_versions in
if previous = zero then raise Not_found
else previous
(* CLI version extended with provenance *)
module Sourced = struct
type nonrec t = t * OpamStateTypes.provenance
let current = current, `Default
let env s =
OpamStd.Option.Op.(s >>= of_string_opt >>| (fun c -> c, `Env))
end
module Op = struct
let ( @>= ) (c,_) = Stdlib.( >= ) c
let ( @< ) (c,_) = Stdlib.( < ) c
let ( @= ) (c,_) = Stdlib.( = ) c
end
module O = struct
type nonrec t = t
let to_string = to_string
let to_json = to_json
let of_json = of_json
let compare = compare
end
module Set = OpamStd.Set.Make(O)
module Map = OpamStd.Map.Make(O)