Skip to content

Commit

Permalink
Do not pass -I <stdlib-dir>
Browse files Browse the repository at this point in the history
  • Loading branch information
jeremiedimino committed Feb 6, 2018
1 parent a1c02df commit 27293e0
Show file tree
Hide file tree
Showing 7 changed files with 20 additions and 14 deletions.
3 changes: 2 additions & 1 deletion src/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -718,7 +718,8 @@ Add it to your jbuild file to remove this warning.
[ Dyn (fun (_, flags,_) -> As flags)
; A "-o"; Target exe
; Dyn (fun (_, _, link_flags) -> As (link_custom @ link_flags))
; Dyn (fun ((libs, _), _, _) -> Lib.link_flags libs ~mode)
; Dyn (fun ((libs, _), _, _) -> Lib.link_flags libs ~mode
~stdlib_dir:ctx.stdlib_dir)
; Dyn (fun ((_, cm_files), _, _) -> Deps cm_files)
]);
if mode = Mode.Byte then
Expand Down
11 changes: 6 additions & 5 deletions src/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,12 +23,13 @@ let dir = function
| Internal (dir, _) -> dir
| External pkg -> pkg.dir

let include_paths ts =
let include_paths ts ~stdlib_dir =
List.fold_left ts ~init:Path.Set.empty ~f:(fun acc t ->
Path.Set.add (dir t) acc)
|> Path.Set.remove stdlib_dir

let include_flags ts =
let dirs = include_paths ts in
let include_flags ts ~stdlib_dir =
let dirs = include_paths ts ~stdlib_dir in
Arg_spec.S (List.concat_map (Path.Set.elements dirs) ~f:(fun dir ->
[Arg_spec.A "-I"; Path dir]))

Expand All @@ -49,9 +50,9 @@ let describe = function
| External pkg ->
sprintf "%s (external)" pkg.name

let link_flags ts ~mode =
let link_flags ts ~mode ~stdlib_dir =
Arg_spec.S
(include_flags ts ::
(include_flags ts ~stdlib_dir ::
List.map ts ~f:(fun t ->
match t with
| External pkg ->
Expand Down
7 changes: 3 additions & 4 deletions src/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,13 +12,12 @@ module Set : Set.S with type elt := t

(*val deps : t -> string list*)

val include_paths : t list -> Path.Set.t

val include_flags : t list -> _ Arg_spec.t
val include_paths : t list -> stdlib_dir:Path.t -> Path.Set.t
val include_flags : t list -> stdlib_dir:Path.t -> _ Arg_spec.t

val c_include_flags : t list -> _ Arg_spec.t

val link_flags : t list -> mode:Mode.t -> _ Arg_spec.t
val link_flags : t list -> mode:Mode.t -> stdlib_dir:Path.t -> _ Arg_spec.t

val archive_files : t list -> mode:Mode.t -> ext_lib:string -> Path.t list

Expand Down
2 changes: 1 addition & 1 deletion src/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@ let build_cm sctx ?sandbox ~dynlink ~flags ~cm_kind ~(dep_graph:Ocamldep.dep_gra
~extra_targets
[ Dyn (fun (_, ocaml_flags) -> As ocaml_flags)
; cmt_args
; Dyn (fun (libs, _) -> Lib.include_flags libs)
; Dyn (fun (libs, _) -> Lib.include_flags libs ~stdlib_dir:ctx.stdlib_dir)
; As extra_args
; if dynlink || cm_kind <> Cmx then As [] else A "-nodynlink"
; A "-no-alias-deps"
Expand Down
3 changes: 2 additions & 1 deletion src/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -173,10 +173,11 @@ let setup_library_rules sctx (lib : Library.t) ~dir ~modules ~mld_files
in
let odoc = get_odoc sctx in
let includes =
let ctx = SC.context sctx in
Build.memoize "includes"
(requires
>>> SC.Doc.deps sctx
>>^ Lib.include_flags)
>>^ Lib.include_flags ~stdlib_dir:ctx.stdlib_dir)
in
let mld_files =
all_mld_files sctx ~dir ~lib ~lib_name ~modules mld_files
Expand Down
2 changes: 1 addition & 1 deletion src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -845,7 +845,7 @@ module PP = struct
>>>
Build.run ~context:ctx (Ok compiler)
[ A "-o" ; Target target
; Dyn (Lib.link_flags ~mode)
; Dyn (Lib.link_flags ~mode ~stdlib_dir:ctx.stdlib_dir)
])

let gen_rules sctx components =
Expand Down
6 changes: 5 additions & 1 deletion src/utop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,11 @@ let add_module_rules sctx ~dir lib_requires =
let utop_ml =
lib_requires
>>^ (fun libs ->
let include_paths = Path.Set.elements (Lib.include_paths libs) in
let include_paths =
let ctx = Super_context.context sctx in
Path.Set.elements
(Lib.include_paths libs ~stdlib_dir:ctx.stdlib_dir)
in
let b = Buffer.create 64 in
let fmt = Format.formatter_of_buffer b in
pp_ml fmt include_paths;
Expand Down

0 comments on commit 27293e0

Please sign in to comment.