Skip to content

Commit

Permalink
Jsoo: refactor version module, add expect tests
Browse files Browse the repository at this point in the history
  • Loading branch information
hhugo committed Jan 6, 2023
1 parent eec5483 commit ac856c9
Show file tree
Hide file tree
Showing 5 changed files with 71 additions and 33 deletions.
2 changes: 1 addition & 1 deletion boot/libs.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
let executables = [ "main" ]

let external_libraries = [ "unix"; "threads" ]
let external_libraries = [ "unix"; "threads.posix"; "threads" ]

let local_libraries =
[ ("otherlibs/ordering", Some "Ordering", false, None)
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/dune_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module Modules = Modules
module Module_compilation = Module_compilation
module Exe_rules = Exe_rules
module Lib_rules = Lib_rules
module Jsoo_rules = Jsoo_rules
module Obj_dir = Obj_dir
module Merlin_ident = Merlin_ident
module Merlin = Merlin
Expand Down
48 changes: 16 additions & 32 deletions src/dune_rules/jsoo_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -75,36 +75,17 @@ end
module Version = struct
type t = int list

let split_char ~sep p =
let len = String.length p in
let rec split beg cur =
if cur >= len then
if cur - beg > 0 then [ String.sub p ~pos:beg ~len:(cur - beg) ] else []
else if sep p.[cur] then
String.sub p ~pos:beg ~len:(cur - beg) :: split (cur + 1) (cur + 1)
else split beg (cur + 1)
in
split 0 0

let split v =
match
split_char
~sep:(function
let of_string s : t =
let s =
match
String.findi s ~f:(function
| '+' | '-' | '~' -> true
| _ -> false)
v
with
| [] -> assert false
| x :: _ ->
List.map
(split_char
~sep:(function
| '.' -> true
| _ -> false)
x)
~f:int_of_string

let of_string : string -> t = split
with
| 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
Expand All @@ -122,7 +103,7 @@ module Version = struct
let* _ = Build_system.build_file bin in
Memo.of_reproducible_fiber
@@ Process.run_capture_line Process.Strict bin [ "--version" ]
|> Memo.map ~f:of_string
|> Memo.map ~f:(fun s -> try Some (of_string s) with _ -> None)

let version_memo =
Memo.create "jsoo-version" ~input:(module Path) impl_version
Expand Down Expand Up @@ -327,9 +308,12 @@ let link_rule cc ~runtime ~target ~obj_dir cm ~flags ~linkall
; [ std_exit ]
])
; As
(match (Version.compare jsoo_verion [ 5; 1 ], linkall) with
| Lt, true | _, false -> []
| (Gt | Eq), true -> [ "--linkall" ])
(match (jsoo_verion, linkall) with
| Some version, true -> (
match Version.compare version [ 5; 1 ] with
| Lt -> []
| Gt | Eq -> [ "--linkall" ])
| None, _ | _, false -> [])
]
in
let spec = Command.Args.S [ Dep (Path.build runtime); Dyn get_all ] in
Expand Down
8 changes: 8 additions & 0 deletions src/dune_rules/jsoo_rules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,14 @@ module Config : sig
val all : t list
end

module Version : sig
type t = int list

val of_string : string -> t

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

val build_cm :
Super_context.t
-> dir:Path.Build.t
Expand Down
45 changes: 45 additions & 0 deletions test/expect-tests/jsoo_tests.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
open Stdune
open Dune_rules
open! Dune_engine
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
in
(* equal *)
test "5.0.1" [ 5; 0; 1 ];
[%expect {| = |}];
test "5.0.0" [ 5; 0 ];
[%expect {| = |}];
test "5.0" [ 5; 0; 0 ];
[%expect {| = |}];
test "5.0+1" [ 5; 0; 0 ];
[%expect {| = |}];
test "5.0~1" [ 5; 0; 0 ];
[%expect {| = |}];
test "5.0+1" [ 5; 0; 0 ];
[%expect {| = |}];
test "5.0.1+git-5.0.1-14-g904cf100b0" [ 5; 0; 1 ];
[%expect {| = |}];

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

0 comments on commit ac856c9

Please sign in to comment.