Skip to content

Commit

Permalink
CR
Browse files Browse the repository at this point in the history
  • Loading branch information
hhugo committed Jan 12, 2023
1 parent 4a5cb08 commit 22e33d7
Show file tree
Hide file tree
Showing 3 changed files with 47 additions and 46 deletions.
40 changes: 18 additions & 22 deletions src/dune_rules/jsoo_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -73,9 +73,9 @@ end = struct
end

module Version = struct
type t = int list
type t = int * int

let of_string s : t =
let of_string s : t option =
let s =
match
String.findi s ~f:(function
Expand All @@ -85,38 +85,34 @@ module Version = struct
| None -> s
| Some i -> String.take s i
in
String.split s ~on:'.' |> List.map ~f:int_of_string

let rec compare v v' =
match (v, v') with
| [ x ], [ y ] -> Int.compare x y
| [], [] -> Ordering.Eq
| [], y :: _ -> Int.compare 0 y
| x :: _, [] -> Int.compare x 0
| x :: xs, y :: ys -> (
match Int.compare x y with
| Eq -> compare xs ys
| n -> n)
try
match String.split s ~on:'.' with
| [] -> None
| [ major ] -> Some (int_of_string major, 0)
| major :: minor :: _ -> Some (int_of_string major, int_of_string minor)
with _ -> None

let compare (ma1, mi1) (ma2, mi2) =
match Int.compare ma1 ma2 with
| Eq -> Int.compare mi1 mi2
| n -> n

let impl_version bin =
let open Memo.O in
let* _ = Build_system.build_file bin in
Memo.of_reproducible_fiber
@@ Process.run_capture_line Process.Strict bin [ "--version" ]
|> Memo.map ~f:(fun s -> try Some (of_string s) with _ -> None)
|> Memo.map ~f:of_string

let version_memo =
Memo.create "jsoo-version" ~input:(module Path) impl_version

let jsoo_verion path =
let open Memo.O in
let* jsoo = path in
let+ jsoo_verion =
match jsoo with
| Ok jsoo_path -> Memo.exec version_memo jsoo_path
| Error e -> Action.Prog.Not_found.raise e
in
jsoo_verion
match jsoo with
| Ok jsoo_path -> Memo.exec version_memo jsoo_path
| Error e -> Action.Prog.Not_found.raise e
end

let install_jsoo_hint = "opam install js_of_ocaml-compiler"
Expand Down Expand Up @@ -310,7 +306,7 @@ let link_rule cc ~runtime ~target ~obj_dir cm ~flags ~linkall
; As
(match (jsoo_verion, linkall) with
| Some version, true -> (
match Version.compare version [ 5; 1 ] with
match Version.compare version (5, 1) with
| Lt -> []
| Gt | Eq -> [ "--linkall" ])
| None, _ | _, false -> [])
Expand Down
4 changes: 2 additions & 2 deletions src/dune_rules/jsoo_rules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,9 @@ module Config : sig
end

module Version : sig
type t = int list
type t = int * int

val of_string : string -> t
val of_string : string -> t option

val compare : t -> t -> Ordering.t
end
Expand Down
49 changes: 27 additions & 22 deletions test/expect-tests/jsoo_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,41 +5,46 @@ open! Dune_tests_common

let%expect_test _ =
let test s l =
let c = Jsoo_rules.Version.compare (Jsoo_rules.Version.of_string s) l in
let r =
match c with
| Eq -> "="
| Lt -> "<"
| Gt -> ">"
in
print_endline r
match Jsoo_rules.Version.of_string s with
| None -> print_endline "Could not parse version"
| Some version ->
let c = Jsoo_rules.Version.compare version l in
let r =
match c with
| Eq -> "="
| Lt -> "<"
| Gt -> ">"
in
print_endline r
in
(* equal *)
test "5.0.1" [ 5; 0; 1 ];
test "5.0.1" (5, 0);
[%expect {| = |}];
test "5.0.0" [ 5; 0 ];
test "5.0.0" (5, 0);
[%expect {| = |}];
test "5.0" [ 5; 0; 0 ];
test "5.0" (5, 0);
[%expect {| = |}];
test "5.0+1" [ 5; 0; 0 ];
test "5" (5, 0);
[%expect {| = |}];
test "5.0~1" [ 5; 0; 0 ];
test "5.0+1" (5, 0);
[%expect {| = |}];
test "5.0+1" [ 5; 0; 0 ];
test "5.0~1" (5, 0);
[%expect {| = |}];
test "5.0.1+git-5.0.1-14-g904cf100b0" [ 5; 0; 1 ];
test "5.0+1" (5, 0);
[%expect {| = |}];
test "5.0.1+git-5.0.1-14-g904cf100b0" (5, 0);
[%expect {| = |}];

test "5.0.1" [ 5; 0; 1; 1 ];
test "5.0.1" (5, 1);
[%expect {| < |}];
test "5.0.1.1" [ 5; 0; 1 ];
[%expect {| > |}];
test "4.0.1" [ 5; 0; 1 ];
test "5.0" (5, 1);
[%expect {| < |}];
test "5.0.1" [ 4; 0; 1 ];
test "5.1.1" (5, 0);
[%expect {| > |}];
test "5.0.1" [ 5; 0 ];
test "5.1" (5, 0);
[%expect {| > |}];
test "5.0" [ 5; 0; 1 ];
test "4.0.1" (5, 0);
[%expect {| < |}];
test "5.0.1" (4, 0);
[%expect {| > |}];
()

0 comments on commit 22e33d7

Please sign in to comment.