Skip to content

Commit

Permalink
interpret -I +compiler-libs as -I +ocamlcommon -I +ocamltoplevel etc
Browse files Browse the repository at this point in the history
  • Loading branch information
v-gb committed Dec 6, 2018
1 parent 0097dde commit ea7ee7f
Show file tree
Hide file tree
Showing 15 changed files with 61 additions and 42 deletions.
8 changes: 5 additions & 3 deletions Changes
Expand Up @@ -513,9 +513,11 @@ Working version
pull requests; see CONTRIBUTING.md for more details.
(David Allsopp, review by Damien Doligez and Sébastien Hinderer)

* GPR#1569: install each compiler libs in a separate directory. Code that
builds against, say, ocamlcommon now needs to specify -I +ocamlcommon
instead of -I +compiler-libs (or both for compatibility).
* GPR#1569: install each compiler libs in a separate directory. Code that builds
against, say, ocamlcommon can now specify -I +ocamlcommon, although -I
+compiler-libs still works for compatibility.
External tools using `Misc.expand_directory Config.standard` should use
instead `Clflags.expand_include` to get the same compatibility.
(Valentin Gatien-Baron, review by Nicolás Ojeda Bär)

- GPR#1610: Remove positions from paths
Expand Down
3 changes: 1 addition & 2 deletions debugger/main.ml
Expand Up @@ -148,8 +148,7 @@ exception Found_program_name
let anonymous s =
program_name := Unix_tools.make_absolute s; raise Found_program_name
let add_include d =
default_load_path :=
Misc.expand_directory Config.standard_library d :: !default_load_path
default_load_path := Clflags.expand_include d @ !default_load_path
let set_socket s =
socket_name := s
let set_topdirs_path s =
Expand Down
7 changes: 3 additions & 4 deletions driver/compmisc.ml
Expand Up @@ -32,10 +32,9 @@ let init_path ?(dir="") native =
let dirs =
!last_include_dirs @ dirs @ Config.flexdll_dirs @ !first_include_dirs
in
let exp_dirs =
List.map (Misc.expand_directory Config.standard_library) dirs in
Config.load_path := dir ::
List.rev_append exp_dirs (Clflags.std_include_dirs ());
let exp_dirs = List.concat (List.map Clflags.expand_include dirs) in
Config.load_path :=
dir :: List.rev_append exp_dirs (Clflags.std_include_dirs ());
Env.reset_cache ()

(* Return the initial environment in which compilation proceeds. *)
Expand Down
7 changes: 4 additions & 3 deletions driver/makedepend.ml
Expand Up @@ -71,9 +71,10 @@ let add_to_list li s =

let add_to_load_path dir =
try
let dir = Misc.expand_directory Config.standard_library dir in
let contents = readdir dir in
add_to_list load_path (dir, contents)
List.iter (fun dir ->
let contents = readdir dir in
add_to_list load_path (dir, contents)
) (Clflags.expand_include dir)
with Sys_error msg ->
Format.fprintf Format.err_formatter "@[Bad -I option: %s@]@." msg;
error_occurred := true
Expand Down
6 changes: 4 additions & 2 deletions tools/.depend
Expand Up @@ -68,8 +68,10 @@ ocamlcp.cmo : ../driver/main_args.cmi
ocamlcp.cmx : ../driver/main_args.cmx
ocamldep.cmo : ../driver/makedepend.cmi
ocamldep.cmx : ../driver/makedepend.cmx
ocamlmklib.cmo : ocamlmklibconfig.cmo ../utils/misc.cmi ../utils/config.cmi
ocamlmklib.cmx : ocamlmklibconfig.cmx ../utils/misc.cmx ../utils/config.cmx
ocamlmklib.cmo : ocamlmklibconfig.cmo ../utils/config.cmi \
../utils/clflags.cmi
ocamlmklib.cmx : ocamlmklibconfig.cmx ../utils/config.cmx \
../utils/clflags.cmx
ocamlmklibconfig.cmo :
ocamlmklibconfig.cmx :
ocamlmktop.cmo : ../utils/ccomp.cmi
Expand Down
3 changes: 2 additions & 1 deletion tools/Makefile
Expand Up @@ -147,7 +147,8 @@ installopt::
# To help building mixed-mode libraries (OCaml + C)

$(call byte_and_opt,ocamlmklib,ocamlmklibconfig.cmo config.cmo \
build_path_prefix_map.cmo misc.cmo ocamlmklib.cmo,)
build_path_prefix_map.cmo misc.cmo identifiable.cmo numbers.cmo \
arg_helper.cmo clflags.cmo ocamlmklib.cmo,)


ocamlmklibconfig.ml: $(ROOTDIR)/Makefile.config Makefile
Expand Down
4 changes: 1 addition & 3 deletions tools/ocamlmklib.ml
Expand Up @@ -279,9 +279,7 @@ let transl_path s =

let flexdll_dirs =
let dirs =
let expand = Misc.expand_directory Config.standard_library in
List.map expand Config.flexdll_dirs
in
List.concat (List.map Clflags.expand_include Config.flexdll_dirs) in
let f dir =
let dir =
if String.contains dir ' ' then
Expand Down
9 changes: 5 additions & 4 deletions toplevel/opttopdirs.ml
Expand Up @@ -33,14 +33,15 @@ let _ = Hashtbl.add directive_table "quit" (Directive_none dir_quit)
(* To add a directory to the load path *)

let dir_directory s =
let d = expand_directory Config.standard_library s in
Config.load_path := d :: !Config.load_path
let d = Clflags.expand_include s in
Config.load_path := d @ !Config.load_path

let _ = Hashtbl.add directive_table "directory" (Directive_string dir_directory)
(* To remove a directory from the load path *)
let dir_remove_directory s =
let d = expand_directory Config.standard_library s in
Config.load_path := List.filter (fun d' -> d' <> d) !Config.load_path
let d = Clflags.expand_include s in
Config.load_path :=
List.filter (fun d' -> not (List.mem d' d)) !Config.load_path

let _ =
Hashtbl.add directive_table "remove_directory"
Expand Down
10 changes: 5 additions & 5 deletions toplevel/opttoploop.ml
Expand Up @@ -543,14 +543,14 @@ let set_paths () =
(* Add whatever -I options have been specified on the command line,
but keep the directories that user code linked in with ocamlmktop
may have added to load_path. *)
let expand = Misc.expand_directory Config.standard_library in
let expand = Clflags.expand_include in
load_path := List.concat [
[ "" ];
List.map expand (List.rev !Compenv.first_include_dirs);
List.map expand (List.rev !Clflags.include_dirs);
List.map expand (List.rev !Compenv.last_include_dirs);
List.concat (List.map expand (List.rev !Compenv.first_include_dirs));
List.concat (List.map expand (List.rev !Clflags.include_dirs));
List.concat (List.map expand (List.rev !Compenv.last_include_dirs));
!load_path;
[expand "+camlp4"];
expand "+camlp4";
]

let initialize_toplevel_env () =
Expand Down
13 changes: 7 additions & 6 deletions toplevel/topdirs.ml
Expand Up @@ -69,9 +69,9 @@ let _ = add_directive "quit" (Directive_none dir_quit)
(* To add a directory to the load path *)

let dir_directory s =
let d = expand_directory Config.standard_library s in
Config.load_path := d :: !Config.load_path;
Dll.add_path [d]
let d = Clflags.expand_include s in
Config.load_path := d @ !Config.load_path;
Dll.add_path d

let _ = add_directive "directory" (Directive_string dir_directory)
{
Expand All @@ -82,9 +82,10 @@ let _ = add_directive "directory" (Directive_string dir_directory)

(* To remove a directory from the load path *)
let dir_remove_directory s =
let d = expand_directory Config.standard_library s in
Config.load_path := List.filter (fun d' -> d' <> d) !Config.load_path;
Dll.remove_path [d]
let d = Clflags.expand_include s in
Config.load_path :=
List.filter (fun d' -> not (List.mem d' d)) !Config.load_path;
Dll.remove_path d

let _ = add_directive "remove_directory" (Directive_string dir_remove_directory)
{
Expand Down
10 changes: 5 additions & 5 deletions toplevel/toploop.ml
Expand Up @@ -503,14 +503,14 @@ let set_paths () =
(* Add whatever -I options have been specified on the command line,
but keep the directories that user code linked in with ocamlmktop
may have added to load_path. *)
let expand = Misc.expand_directory Config.standard_library in
let expand = Clflags.expand_include in
load_path := List.concat [
[ "" ];
List.map expand (List.rev !Compenv.first_include_dirs);
List.map expand (List.rev !Clflags.include_dirs);
List.map expand (List.rev !Compenv.last_include_dirs);
List.concat (List.map expand (List.rev !Compenv.first_include_dirs));
List.concat (List.map expand (List.rev !Clflags.include_dirs));
List.concat (List.map expand (List.rev !Compenv.last_include_dirs));
!load_path;
[expand "+camlp4"];
expand "+camlp4";
];
Dll.add_path !load_path

Expand Down
4 changes: 2 additions & 2 deletions utils/ccomp.ml
Expand Up @@ -102,8 +102,8 @@ let compile_file ?output ?(opt="") ?stable_name name =
(if !Clflags.debug && Config.ccomp_type <> "msvc" then "-g" else "")
(String.concat " " (List.rev !Clflags.all_ccopts))
(quote_prefixed "-I"
(List.map (Misc.expand_directory Config.standard_library)
(List.rev !Clflags.include_dirs)))
(List.concat (List.map Clflags.expand_include
(List.rev !Clflags.include_dirs))))
(String.concat " " (Clflags.std_include_flags "-I"))
(Filename.quote name)
(* cl tediously includes the name of the C file as the first thing it
Expand Down
15 changes: 15 additions & 0 deletions utils/clflags.ml
Expand Up @@ -169,6 +169,21 @@ let std_include_dirs () =
let std_include_flags prefix =
List.map (fun dir -> prefix ^ Filename.quote dir) (std_include_dirs ())

let expand_include =
let expand_one = Misc.expand_directory Config.standard_library in
fun s ->
match s with
| "+compiler-libs" ->
List.map expand_one
[ s;
"+ocamlcommon";
"+ocamlbytecomp";
"+ocamloptcomp";
"+ocamltoplevel";
"+ocamlopttoplevel";
]
| _ -> [ expand_one s ]

let shared = ref false (* -shared *)
let dlcode = ref true (* not -nodynlink *)

Expand Down
1 change: 1 addition & 0 deletions utils/clflags.mli
Expand Up @@ -183,6 +183,7 @@ val inline_branch_factor : Float_arg_helper.parsed ref
val dont_write_files : bool ref
val std_include_flags : string -> string list
val std_include_dirs : unit -> string list
val expand_include : string -> string list
val shared : bool ref
val dlcode : bool ref
val pic_code : bool ref
Expand Down
3 changes: 1 addition & 2 deletions utils/misc.ml
Expand Up @@ -280,8 +280,7 @@ let remove_file filename =

let expand_directory alt s =
if String.length s > 0 && s.[0] = '+'
then Filename.concat alt
(String.sub s 1 (String.length s - 1))
then Filename.concat alt (String.sub s 1 (String.length s - 1))
else s

let path_separator =
Expand Down

0 comments on commit ea7ee7f

Please sign in to comment.