Skip to content

Commit

Permalink
js_of_ocaml: look for runtime in the same dir as executable if ocamlf…
Browse files Browse the repository at this point in the history
…ind pkg unavailable (#1467)

Signed-off-by: nojebar <[email protected]>
  • Loading branch information
nojb authored and jeremiedimino committed Dec 19, 2018
1 parent 39d07ba commit ee6123c
Showing 1 changed file with 27 additions and 12 deletions.
39 changes: 27 additions & 12 deletions src/js_of_ocaml_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,29 +19,44 @@ let install_jsoo_hint = "try: opam install js_of_ocaml-compiler"
let in_build_dir ~ctx args =
Path.L.relative ctx.Context.build_dir (".js" :: args)

let runtime_file ~sctx file =
let jsoo ~dir sctx =
SC.resolve_program sctx ~dir ~loc:None ~hint:install_jsoo_hint
"js_of_ocaml"

let runtime_file ~dir ~sctx file =
match
Artifacts.file_of_lib (SC.artifacts sctx)
~loc:Loc.none
~lib:(Lib_name.of_string_exn ~loc:None "js_of_ocaml-compiler") ~file
with
| Error _ ->
Arg_spec.Dyn (fun _ ->
Utils.library_not_found ~context:(SC.context sctx).name
~hint:install_jsoo_hint
"js_of_ocaml-compiler")
| Ok f -> Arg_spec.Dep f
let fail =
let fail () =
Utils.library_not_found ~context:(SC.context sctx).name
~hint:install_jsoo_hint
"js_of_ocaml-compiler"
in
Build.fail {fail}
in
begin match jsoo ~dir sctx with
| Ok path ->
let path = Path.relative (Path.parent_exn path) file in
Build.if_file_exists path ~then_:(Build.arr (fun _ -> path)) ~else_:fail
| _ ->
fail
end
| Ok f ->
Build.arr (fun _ -> f)

let js_of_ocaml_rule sctx ~dir ~flags ~spec ~target =
let jsoo =
SC.resolve_program sctx ~dir ~loc:None ~hint:install_jsoo_hint
"js_of_ocaml" in
let runtime = runtime_file ~sctx "runtime.js" in
let jsoo = jsoo ~dir sctx in
(Build.arr (fun x -> x) &&& runtime_file ~dir ~sctx "runtime.js") >>>
Build.run ~dir
jsoo
[ Arg_spec.Dyn flags
[ Arg_spec.Dyn (fun (x, _) -> flags x)
; Arg_spec.A "-o"; Target target
; Arg_spec.A "--no-runtime"; runtime
; Arg_spec.A "--no-runtime"
; Arg_spec.Dyn (fun (_, runtime) -> Dep runtime)
; spec
]

Expand Down

0 comments on commit ee6123c

Please sign in to comment.