Skip to content

Commit

Permalink
Merge branch 'pr/238'
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Sep 6, 2017
2 parents a7067f5 + 6a3c51c commit 1da474b
Show file tree
Hide file tree
Showing 3 changed files with 31 additions and 1 deletion.
25 changes: 24 additions & 1 deletion src/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,12 @@ module Gen(P : Params) = struct
else
fun x -> x
in
let objs (cm, _, _, _) =
if mode = Mode.Byte then
[]
else
List.map ~f:(Path.change_extension ~ext:ctx.ext_obj) cm
in
SC.add_rule sctx
(Build.fanout4
(dep_graph >>>
Expand All @@ -100,6 +106,8 @@ module Gen(P : Params) = struct
(Ocaml_flags.get flags mode)
(SC.expand_and_eval_set sctx ~scope ~dir lib.library_flags ~standard:[])
>>>
Build.dyn_paths (Build.arr objs)
>>>
Build.run ~context:ctx (Dep compiler)
~extra_targets:(
match mode with
Expand Down Expand Up @@ -376,6 +384,8 @@ module Gen(P : Params) = struct
let src = lib_archive lib ~dir ~ext:(Mode.compiled_lib_ext Native) in
let dst = lib_archive lib ~dir ~ext:".cmxs" in
let build =
Build.dyn_paths (Build.arr (fun () -> [lib_archive lib ~dir ~ext:ctx.ext_lib]))
>>>
Ocaml_flags.get flags Native
>>>
Build.run ~context:ctx
Expand Down Expand Up @@ -440,8 +450,21 @@ module Gen(P : Params) = struct
~mode
[String.capitalize_ascii name]))
in
let objs (libs, cm) =
if mode = Mode.Byte then
[]
else
let libs =
let f = function
| Lib.Internal (dir, lib) -> Some (Path.relative dir (lib.name ^ ctx.ext_lib))
| External _ -> None
in
List.filter_map ~f libs
in
libs @ List.map ~f:(Path.change_extension ~ext:ctx.ext_obj) cm
in
SC.add_rule sctx
(libs_and_cm
((libs_and_cm >>> Build.dyn_paths (Build.arr objs))
&&&
Build.fanout
(Ocaml_flags.get flags mode)
Expand Down
4 changes: 4 additions & 0 deletions src/path.ml
Original file line number Diff line number Diff line change
Expand Up @@ -411,3 +411,7 @@ let rm_rf =
match Unix.lstat fn with
| exception Unix.Unix_error(ENOENT, _, _) -> ()
| _ -> loop fn

let change_extension ~ext t =
let t = try Filename.chop_extension t with Not_found -> t in
t ^ ext
3 changes: 3 additions & 0 deletions src/path.mli
Original file line number Diff line number Diff line change
Expand Up @@ -101,3 +101,6 @@ val rmdir : t -> unit
val unlink : t -> unit
val unlink_no_err : t -> unit
val rm_rf : t -> unit

(** Changes the extension of the filename (or adds an extension if there was none) *)
val change_extension : ext:string -> t -> t

0 comments on commit 1da474b

Please sign in to comment.