Skip to content

Commit

Permalink
Merge branch 'main' into haiku
Browse files Browse the repository at this point in the history
  • Loading branch information
anmonteiro authored Sep 29, 2024
2 parents 3bf143c + 9f3cda7 commit cf7c23b
Show file tree
Hide file tree
Showing 15 changed files with 62 additions and 16 deletions.
2 changes: 1 addition & 1 deletion bench/micro/dune
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@
(library_flags -linkall)
(preprocess
(pps ppx_bench))
(libraries dune_thread_pool threads.posix core_bench.inline_benchmarks))
(libraries dune_thread_pool unix threads.posix core_bench.inline_benchmarks))

(executable
(name thread_pool_bench_main)
Expand Down
1 change: 1 addition & 0 deletions doc/changes/10935.md
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
- Forward the linkall flag to jsoo in whole program compilation as well (#10935, @hhugo)
6 changes: 3 additions & 3 deletions flake.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

10 changes: 8 additions & 2 deletions otherlibs/stdune/src/stdune.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,11 @@
[@@@alert unstable "The API of this library is not stable and may change without notice."]
[@@@alert "-unstable"]
include struct
[@@@ocaml.warning "-53"]

[@@@alert
unstable "The API of this library is not stable and may change without notice."]

[@@@alert "-unstable"]
end

module Appendable_list = Appendable_list
module Nonempty_list = Nonempty_list
Expand Down
1 change: 1 addition & 0 deletions src/dune_lang/package_version.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ type t

val of_string : string -> t
val of_string_opt : string -> t option
val of_string_user_error : Loc.t * string -> (t, User_message.t) result
val to_string : t -> string
val equal : t -> t -> bool
val to_dyn : t -> Dyn.t
Expand Down
20 changes: 13 additions & 7 deletions src/dune_pkg/opam_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,13 +57,15 @@ let parse =

let parse_value = parse_gen OpamBaseParser.value

let get_field t name =
let get_field_with_pos t name =
List.find_map t.file_contents ~f:(fun value ->
match value.pelem with
| Variable (var, value) when var.pelem = name -> Some value
| Variable (var, value) when var.pelem = name -> Some (value, var.pos)
| _ -> None)
;;

let get_field t name = get_field_with_pos t name |> Option.map ~f:fst

let absolutify_positions ~file_contents t =
let bols = ref [ 0 ] in
String.iteri file_contents ~f:(fun i ch -> if ch = '\n' then bols := (i + 1) :: !bols);
Expand Down Expand Up @@ -225,15 +227,16 @@ let load_opam_file_with_contents ~contents:opam_file_string file name =
None
in
let open Option.O in
let get_one name =
let* value =
let get_one_with_loc name =
let* value, pos =
let* opam = opam in
get_field opam name
get_field_with_pos opam name
in
match value.pelem with
| String s -> Some s
| String s -> Some (loc_of_opam_pos pos, s)
| _ -> None
in
let get_one name = get_one_with_loc name >>| snd in
let get_many name =
let* value =
let* opam = opam in
Expand Down Expand Up @@ -270,7 +273,10 @@ let load_opam_file_with_contents ~contents:opam_file_string file name =
~name
~dir
~loc
~version:(get_one "version" |> Option.map ~f:Package_version.of_string)
~version:
(get_one_with_loc "version"
|> Option.map ~f:Package_version.of_string_user_error
>>| User_error.ok_exn)
~conflicts:[]
~depends:[]
~depopts:[]
Expand Down
1 change: 1 addition & 0 deletions src/dune_pkg/package_version.mli
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ open! Stdune
type t = Dune_lang.Package_version.t

val of_string : string -> t
val of_string_user_error : Loc.t * string -> (t, User_message.t) result
val to_string : t -> string
val equal : t -> t -> bool
val to_dyn : t -> Dyn.t
Expand Down
20 changes: 18 additions & 2 deletions src/dune_rules/jsoo/jsoo_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -291,10 +291,25 @@ let standalone_runtime_rule cc ~javascript_files ~target ~flags =
~config:(Some config)
;;

let exe_rule cc ~javascript_files ~src ~target ~flags =
let exe_rule cc ~linkall ~javascript_files ~src ~target ~flags =
let dir = Compilation_context.dir cc in
let sctx = Compilation_context.super_context cc in
let libs = Compilation_context.requires_link cc in
let linkall =
let open Action_builder.O in
let+ linkall = linkall
and+ jsoo_version =
let* jsoo = jsoo ~dir sctx in
Action_builder.of_memo @@ Version.jsoo_version jsoo
in
Command.Args.As
(match jsoo_version, linkall with
| Some version, true ->
(match Version.compare version (5, 1) with
| Lt -> []
| Gt | Eq -> [ "--linkall" ])
| None, _ | _, false -> [])
in
let spec =
Command.Args.S
[ Resolve.Memo.args
Expand All @@ -303,6 +318,7 @@ let exe_rule cc ~javascript_files ~src ~target ~flags =
Command.Args.Deps (jsoo_runtime_files libs))
; Deps (List.map ~f:Path.build javascript_files)
; Dep (Path.build src)
; Dyn linkall
]
in
js_of_ocaml_rule sctx ~sub_command:Compile ~dir ~spec ~target ~flags ~config:None
Expand Down Expand Up @@ -549,7 +565,7 @@ let build_exe
in
()
| Whole_program ->
exe_rule cc ~javascript_files ~src ~target ~flags ~sourcemap
exe_rule cc ~linkall ~javascript_files ~src ~target ~flags ~sourcemap
|> Super_context.add_rule sctx ~loc ~dir ~mode
;;

Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/jsoo/inline-tests.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ Run inline tests using node js
inline tests (JS)

$ dune runtest --profile release
Warning: your program contains effect handlers; you should probably run js_of_ocaml with option '--enable=effects'
inline tests (JS)
inline tests (JS)
inline tests (Native)
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 3.16)
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
opam-version: "2.0"
version: ""
9 changes: 9 additions & 0 deletions test/blackbox-tests/test-cases/package-version-empty.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
Testing dune #10674 where an empty version in an opam file caused a code error
in dune. We should make sure that this case is handled gracefully.

$ dune build
File "foo.opam", line 2, characters 0-7:
2 | version: ""
^^^^^^^
Error: "" is an invalid package version.
[1]
1 change: 1 addition & 0 deletions test/expect-tests/dune_file_watcher/dune
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@
(deps
(sandbox always)))
(libraries
unix
dune_file_watcher
dune_file_watcher_tests_lib
ppx_expect.config
Expand Down
1 change: 1 addition & 0 deletions test/expect-tests/fsevents/dune
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
(deps
(sandbox always)))
(libraries
unix
fsevents
stdune
threads.posix
Expand Down
2 changes: 1 addition & 1 deletion test/unit-tests/fswatch_win/dune
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
(executable
(name fswatch_win_tests)
(libraries fswatch_win stdune))
(libraries fswatch_win unix stdune))

(rule
(alias fswatch_win_tests)
Expand Down

0 comments on commit cf7c23b

Please sign in to comment.