Skip to content

Commit

Permalink
Jsoo: don't ignore linkall
Browse files Browse the repository at this point in the history
  • Loading branch information
hhugo committed Jan 5, 2023
1 parent 07e285f commit fcd2db7
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 3 deletions.
33 changes: 31 additions & 2 deletions src/dune_rules/exe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -202,15 +202,44 @@ let link_exe ~loc ~name ~(linkage : Linkage.t) ~cm_files ~link_time_code_gen
| Some p -> Promote p)
action_with_targets

let command_args_has_flag ~f args =
let rec has_flag : 'a. 'a Command.Args.t -> bool Action_builder.t =
fun (type a) (a : a Command.Args.t) ->
match a with
| Command.Args.A a -> Action_builder.return (f a)
| As l -> Action_builder.return (List.exists l ~f)
| S l ->
Action_builder.all (List.map l ~f:has_flag)
|> Action_builder.map ~f:(List.exists ~f:(fun x -> x))
| Concat (s, l) ->
if f s then Action_builder.return true
else
Action_builder.all (List.map l ~f:has_flag)
|> Action_builder.map ~f:(List.exists ~f:(fun x -> x))
| Dyn a -> has_flag_action_builder a
| Dep _
| Deps _
| Target _
| Path _
| Paths _
| Hidden_deps _
| Hidden_targets _
| Fail _
| Expand _ -> Action_builder.return false
and has_flag_action_builder a =
Action_builder.bind a ~f:(fun t -> has_flag t)
in
has_flag args

let link_js ~name ~loc ~obj_dir ~top_sorted_modules ~link_args ~promote
~link_time_code_gen cctx =
let in_context =
CC.js_of_ocaml cctx |> Option.value ~default:Js_of_ocaml.In_context.default
in
let src = exe_path_from_name cctx ~name ~linkage:Linkage.byte_for_jsoo in
let linkall =
ignore link_args;
Action_builder.return false
Action_builder.bind link_args
~f:(command_args_has_flag ~f:(String.equal "-linkall"))
in
Jsoo_rules.build_exe cctx ~loc ~obj_dir ~in_context ~src ~top_sorted_modules
~promote ~link_time_code_gen ~linkall
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/jsoo_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -248,7 +248,6 @@ let link_rule cc ~runtime ~target ~obj_dir cm ~flags ~linkall
[ "stdlib"; "std_exit" ^ Js_of_ocaml.Ext.cmo ])
in
let linkall = force_linkall || force_linkall2 in
ignore linkall;
Command.Args.S
[ Deps
(List.concat
Expand All @@ -258,6 +257,7 @@ let link_rule cc ~runtime ~target ~obj_dir cm ~flags ~linkall
; all_other_modules
; [ std_exit ]
])
; (if linkall then A "-linkall" else As [])
]
in
let spec = Command.Args.S [ Dep (Path.build runtime); Dyn get_all ] in
Expand Down

0 comments on commit fcd2db7

Please sign in to comment.