diff --git a/boot/libs.ml b/boot/libs.ml index 9e03f1aa4bde..51dd96685f70 100644 --- a/boot/libs.ml +++ b/boot/libs.ml @@ -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) diff --git a/src/dune_rules/dune_rules.ml b/src/dune_rules/dune_rules.ml index a3a8ff2a4a0b..1f980da9e4b7 100644 --- a/src/dune_rules/dune_rules.ml +++ b/src/dune_rules/dune_rules.ml @@ -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 diff --git a/src/dune_rules/jsoo_rules.ml b/src/dune_rules/jsoo_rules.ml index 7cf8b4dfd90e..1ad640373e31 100644 --- a/src/dune_rules/jsoo_rules.ml +++ b/src/dune_rules/jsoo_rules.ml @@ -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 @@ -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 @@ -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 diff --git a/src/dune_rules/jsoo_rules.mli b/src/dune_rules/jsoo_rules.mli index ab9042f242c8..c04beabe2b11 100644 --- a/src/dune_rules/jsoo_rules.mli +++ b/src/dune_rules/jsoo_rules.mli @@ -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 diff --git a/test/expect-tests/jsoo_tests.ml b/test/expect-tests/jsoo_tests.ml new file mode 100644 index 000000000000..aa43f5d5a23d --- /dev/null +++ b/test/expect-tests/jsoo_tests.ml @@ -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 {| < |}]; + ()