diff options
Diffstat (limited to 'bytecomp')
-rw-r--r-- | bytecomp/bytelibrarian.ml | 7 | ||||
-rw-r--r-- | bytecomp/bytelink.ml | 22 | ||||
-rw-r--r-- | bytecomp/dll.ml | 71 | ||||
-rw-r--r-- | bytecomp/dll.mli | 4 | ||||
-rw-r--r-- | bytecomp/dllpath.ml | 59 | ||||
-rw-r--r-- | bytecomp/dllpath.mli | 25 | ||||
-rw-r--r-- | bytecomp/emitcode.ml | 5 | ||||
-rw-r--r-- | bytecomp/emitcode.mli | 5 |
8 files changed, 76 insertions, 122 deletions
diff --git a/bytecomp/bytelibrarian.ml b/bytecomp/bytelibrarian.ml index 7bece0570..bad04b7a5 100644 --- a/bytecomp/bytelibrarian.ml +++ b/bytecomp/bytelibrarian.ml @@ -41,6 +41,7 @@ let copy_compunit ic oc compunit = let lib_sharedobjs = ref [] let lib_ccobjs = ref [] let lib_ccopts = ref [] +let lib_dllibs = ref [] (* See Bytelink.add_ccobjs for explanations on how options are ordered. Notice that here we scan .cma files given on the command line from @@ -50,7 +51,8 @@ let add_ccobjs l = if not !Clflags.no_auto_link then begin if l.lib_custom then Clflags.custom_runtime := true; lib_ccobjs := !lib_ccobjs @ l.lib_ccobjs; - lib_ccopts := !lib_ccopts @ l.lib_ccopts + lib_ccopts := !lib_ccopts @ l.lib_ccopts; + lib_dllibs := !lib_dllibs @ l.lib_dllibs end let copy_object_file oc name = @@ -96,7 +98,8 @@ let create_archive file_list lib_name = { lib_units = units; lib_custom = !Clflags.custom_runtime; lib_ccobjs = !Clflags.ccobjs @ !lib_ccobjs; - lib_ccopts = !Clflags.ccopts @ !lib_ccopts } in + lib_ccopts = !Clflags.ccopts @ !lib_ccopts; + lib_dllibs = !Clflags.dllibs @ !lib_dllibs } in let pos_toc = pos_out outchan in output_value outchan toc; seek_out outchan ofs_pos_toc; diff --git a/bytecomp/bytelink.ml b/bytecomp/bytelink.ml index c0cffe6a1..2fec10427 100644 --- a/bytecomp/bytelink.ml +++ b/bytecomp/bytelink.ml @@ -43,12 +43,14 @@ type link_action = let lib_ccobjs = ref [] let lib_ccopts = ref [] +let lib_dllibs = ref [] let add_ccobjs l = if not !Clflags.no_auto_link then begin if l.lib_custom then Clflags.custom_runtime := true; lib_ccobjs := l.lib_ccobjs @ !lib_ccobjs; - lib_ccopts := l.lib_ccopts @ !lib_ccopts + lib_ccopts := l.lib_ccopts @ !lib_ccopts; + lib_dllibs := l.lib_dllibs @ !lib_dllibs end (* A note on ccobj ordering: @@ -278,11 +280,9 @@ let link_bytecode tolink exec_name standalone = let start_code = pos_out outchan in Symtable.init(); Hashtbl.clear crc_interfaces; - let sharedobjs = Dll.extract_dll_names !Clflags.ccobjs in + let sharedobjs = List.map Dll.extract_dll_name !Clflags.dllibs in if standalone then begin (* Initialize the DLL machinery *) - if List.length sharedobjs < List.length !Clflags.ccobjs - then raise (Error Require_custom); Dll.add_path !load_path; try Dll.open_dlls sharedobjs with Failure reason -> raise(Error(Cannot_open_dll reason)) @@ -405,17 +405,9 @@ let rec extract suffix l = let build_custom_runtime prim_name exec_name = match Sys.os_type with "Unix" | "Cygwin" -> - let rpath = - if Config.bytecomp_c_rpath = "" then "" else - String.concat ":" - (List.filter ((<>) "") - (!Clflags.dllpaths @ - Dllpath.ld_library_path_contents() @ - Dllpath.ld_conf_contents())) - in Ccomp.command (Printf.sprintf - "%s -o %s -I%s %s %s %s %s %s -lcamlrun %s" + "%s -o %s -I%s %s %s %s %s -lcamlrun %s" !Clflags.c_linker exec_name Config.standard_library @@ -424,7 +416,6 @@ let build_custom_runtime prim_name exec_name = (String.concat " " (List.map (fun dir -> if dir = "" then "" else "-L" ^ dir) !load_path)) - (if rpath <> "" then Config.bytecomp_c_rpath ^ rpath else "") (String.concat " " (List.rev !Clflags.ccobjs)) Config.bytecomp_c_libraries) | "Win32" -> @@ -500,8 +491,9 @@ let link objfiles = let objfiles = if !Clflags.nopervasives then objfiles else "stdlib.cma" :: (objfiles @ ["std_exit.cmo"]) in let tolink = List.fold_right scan_file objfiles [] in - Clflags.ccobjs := !Clflags.ccobjs @ !lib_ccobjs; + Clflags.ccobjs := !Clflags.ccobjs @ !lib_ccobjs; (* put user's libs last *) Clflags.ccopts := !lib_ccopts @ !Clflags.ccopts; (* put user's opts first *) + Clflags.dllibs := !lib_dllibs @ !Clflags.dllibs; (* put user's DLLs first *) if not !Clflags.custom_runtime then link_bytecode tolink !Clflags.exec_name true else if not !Clflags.output_c_object then begin diff --git a/bytecomp/dll.ml b/bytecomp/dll.ml index e986af2fe..755bffd73 100644 --- a/bytecomp/dll.ml +++ b/bytecomp/dll.ml @@ -38,18 +38,15 @@ let names_of_opened_dlls = ref ([] : string list) let add_path dirs = search_path := dirs @ !search_path -(* Extract names of DLLs from a list of C object files and libraries *) - -let extract_dll_names files = - List.fold_right - (fun file res -> - if Filename.check_suffix file Config.ext_dll then - Filename.chop_suffix file Config.ext_dll :: res - else if String.length file >= 2 && String.sub file 0 2 = "-l" then - ("lib" ^ String.sub file 2 (String.length file - 2)) :: res - else - res) - files [] +(* Extract the name of a DLLs from its external name (xxx.so or -lxxx) *) + +let extract_dll_name file = + if Filename.check_suffix file Config.ext_dll then + Filename.chop_suffix file Config.ext_dll + else if String.length file >= 2 && String.sub file 0 2 = "-l" then + "dll" ^ String.sub file 2 (String.length file - 2) + else + file (* will cause error later *) (* Open a list of DLLs, adding them to opened_dlls. Raise [Failure msg] in case of error. *) @@ -104,13 +101,57 @@ let synchronize_primitive num symb = assert (actual_num = num) end +(* Read the [ld.conf] file and return the corresponding list of directories *) + +let ld_conf_contents () = + let path = ref [] in + begin try + let ic = open_in (Filename.concat Config.standard_library "ld.conf") in + begin try + while true do + path := input_line ic :: !path + done + with End_of_file -> () + end; + close_in ic + with Sys_error _ -> () + end; + List.rev !path + +(* Split the CAML_LD_LIBRARY_PATH environment variable and return + the corresponding list of directories. *) + +let split str sep = + let rec split_rec pos = + if pos >= String.length str then [] else begin + try + let newpos = String.index_from str pos sep in + String.sub str pos (newpos - pos) :: + split_rec (newpos + 1) + with Not_found -> + [String.sub str pos (String.length str - pos)] + end in + split_rec 0 + +let ld_library_path_contents () = + let path_separator = + match Sys.os_type with + "Unix" | "Cygwin" -> ':' | "Win32" -> ';' | _ -> assert false in + try + split (Sys.getenv "CAML_LD_LIBRARY_PATH") path_separator + with Not_found -> + [] + +let split_dll_path path = + split path '\000' + (* Initialization for linking in core (dynlink or toplevel) *) let init_toplevel dllpath = search_path := - Dllpath.ld_library_path_contents() @ - Dllpath.split_dll_path dllpath @ - Dllpath.ld_conf_contents(); + ld_library_path_contents() @ + split_dll_path dllpath @ + ld_conf_contents(); opened_dlls := Array.to_list (get_current_dlls()); names_of_opened_dlls := []; linking_in_core := true diff --git a/bytecomp/dll.mli b/bytecomp/dll.mli index 0e79207a9..0be68e2ab 100644 --- a/bytecomp/dll.mli +++ b/bytecomp/dll.mli @@ -14,8 +14,8 @@ (* Handling of dynamically-linked libraries *) -(* Extract names of DLLs from a list of C object files and libraries *) -val extract_dll_names: string list -> string list +(* Extract the name of a DLLs from its external name (xxx.so or -lxxx) *) +val extract_dll_name: string -> string (* Open a list of DLLs, adding them to opened_dlls. Raise [Failure msg] in case of error. *) diff --git a/bytecomp/dllpath.ml b/bytecomp/dllpath.ml deleted file mode 100644 index f0626a871..000000000 --- a/bytecomp/dllpath.ml +++ /dev/null @@ -1,59 +0,0 @@ -(***********************************************************************) -(* *) -(* Objective Caml *) -(* *) -(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) -(* *) -(* Copyright 2001 Institut National de Recherche en Informatique et *) -(* en Automatique. All rights reserved. This file is distributed *) -(* under the terms of the Q Public License version 1.0. *) -(* *) -(***********************************************************************) - -(* $Id$ *) - -(* Handling of load path for dynamically-linked libraries *) - -(* Read the [ld.conf] file and return the corresponding list of directories *) - -let ld_conf_contents () = - let path = ref [] in - begin try - let ic = open_in (Filename.concat Config.standard_library "ld.conf") in - begin try - while true do - path := input_line ic :: !path - done - with End_of_file -> () - end; - close_in ic - with Sys_error _ -> () - end; - List.rev !path - -(* Split the CAML_LD_LIBRARY_PATH environment variable and return - the corresponding list of directories. *) - -let split str sep = - let rec split_rec pos = - if pos >= String.length str then [] else begin - try - let newpos = String.index_from str pos sep in - String.sub str pos (newpos - pos) :: - split_rec (newpos + 1) - with Not_found -> - [String.sub str pos (String.length str - pos)] - end in - split_rec 0 - -let ld_library_path_contents () = - let path_separator = - match Sys.os_type with - "Unix" | "Cygwin" -> ':' | "Win32" -> ';' | _ -> assert false in - try - split (Sys.getenv "CAML_LD_LIBRARY_PATH") path_separator - with Not_found -> - [] - -let split_dll_path path = - split path '\000' diff --git a/bytecomp/dllpath.mli b/bytecomp/dllpath.mli deleted file mode 100644 index 496fbf497..000000000 --- a/bytecomp/dllpath.mli +++ /dev/null @@ -1,25 +0,0 @@ -(***********************************************************************) -(* *) -(* Objective Caml *) -(* *) -(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) -(* *) -(* Copyright 2001 Institut National de Recherche en Informatique et *) -(* en Automatique. All rights reserved. This file is distributed *) -(* under the terms of the Q Public License version 1.0. *) -(* *) -(***********************************************************************) - -(* $Id$ *) - -(* Handling of load path for dynamically-linked libraries *) - -(* Read the [ld.conf] file and return the corresponding list of directories *) -val ld_conf_contents: unit -> string list - -(* Split the CAML_LD_LIBRARY_PATH environment variable and return - the corresponding list of directories *) -val ld_library_path_contents: unit -> string list - -(* Split the given 0-separated path *) -val split_dll_path: string -> string list diff --git a/bytecomp/emitcode.ml b/bytecomp/emitcode.ml index c84159b51..01fbde4ba 100644 --- a/bytecomp/emitcode.ml +++ b/bytecomp/emitcode.ml @@ -48,8 +48,9 @@ type compilation_unit = type library = { lib_units: compilation_unit list; (* List of compilation units *) lib_custom: bool; (* Requires custom mode linking? *) - lib_ccobjs: string list; (* C object files needed *) - lib_ccopts: string list } (* Extra opts to C compiler *) + lib_ccobjs: string list; (* C object files needed for -custom *) + lib_ccopts: string list; (* Extra opts to C compiler *) + lib_dllibs: string list } (* DLLs needed *) (* Buffering of bytecode *) diff --git a/bytecomp/emitcode.mli b/bytecomp/emitcode.mli index e38ef8644..481ad506b 100644 --- a/bytecomp/emitcode.mli +++ b/bytecomp/emitcode.mli @@ -49,8 +49,9 @@ type compilation_unit = type library = { lib_units: compilation_unit list; (* List of compilation units *) lib_custom: bool; (* Requires custom mode linking? *) - lib_ccobjs: string list; (* C object files needed *) - lib_ccopts: string list } (* Extra opts to C compiler *) + lib_ccobjs: string list; (* C object files needed for -custom *) + lib_ccopts: string list; (* Extra opts to C compiler *) + lib_dllibs: string list } (* DLLs needed *) (* Format of a .cma file: magic number (Config.cma_magic_number) |