(**************************************************************************) (* *) (* OCaml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) (* Copyright 1996 Institut National de Recherche en Informatique et *) (* en Automatique. *) (* *) (* All rights reserved. This file is distributed under the terms of *) (* the GNU Lesser General Public License version 2.1, with the *) (* special exception on linking described in the file LICENSE. *) (* *) (**************************************************************************) (* Link a set of .cmo files and produce a bytecode executable. *) open Misc open Config open Cmo_format module String = Misc.Stdlib.String module Compunit = Symtable.Compunit module Dep = struct type t = compunit * compunit let compare = compare end module DepSet = Set.Make (Dep) type error = | File_not_found of filepath | Not_an_object_file of filepath | Wrong_object_name of filepath | Symbol_error of filepath * Symtable.error | Inconsistent_import of modname * filepath * filepath | Custom_runtime | File_exists of filepath | Cannot_open_dll of filepath | Camlheader of string * filepath | Link_error of Linkdeps.error | Needs_custom_runtime of string exception Error of error type link_action = Link_object of string * compilation_unit (* Name of .cmo file and descriptor of the unit *) | Link_archive of string * compilation_unit list (* Name of .cma file and descriptors of the units to be linked. *) (* Add C objects and options from a library descriptor *) (* Ignore them if -noautolink or -use-runtime or -use-prim was given *) let lib_ccobjs = ref [] let lib_ccopts = ref [] let lib_dllibs = ref [] let add_ccobjs obj_name origin l = if not !Clflags.no_auto_link then begin if String.length !Clflags.use_runtime = 0 && String.length !Clflags.use_prims = 0 then begin if l.lib_custom then Clflags.custom_runtime := true; lib_ccobjs := l.lib_ccobjs @ !lib_ccobjs; let replace_origin = Misc.replace_substring ~before:"$CAMLORIGIN" ~after:origin in lib_ccopts := List.map replace_origin l.lib_ccopts @ !lib_ccopts; end else if l.lib_custom then raise(Error(Needs_custom_runtime obj_name)); lib_dllibs := l.lib_dllibs @ !lib_dllibs end (* A note on ccobj ordering: - Clflags.ccobjs is in reverse order w.r.t. what was given on the ocamlc command line; - l.lib_ccobjs is also in reverse order w.r.t. what was given on the ocamlc -a command line when the library was created; - Clflags.ccobjs is reversed just before calling the C compiler for the custom link; - .cma files on the command line of ocamlc are scanned right to left; - Before linking, we add lib_ccobjs after Clflags.ccobjs. Thus, for ocamlc a.cma b.cma obj1 obj2 where a.cma was built with ocamlc -i ... obja1 obja2 and b.cma was built with ocamlc -i ... objb1 objb2 lib_ccobjs starts as [], becomes objb2 objb1 when b.cma is scanned, then obja2 obja1 objb2 objb1 when a.cma is scanned. Clflags.ccobjs was initially obj2 obj1. and is set to obj2 obj1 obja2 obja1 objb2 objb1. Finally, the C compiler is given objb1 objb2 obja1 obja2 obj1 obj2, which is what we need. (If b depends on a, a.cma must appear before b.cma, but b's C libraries must appear before a's C libraries.) *) (* First pass: determine which units are needed *) let required compunit = (Symtable.required_compunits compunit.cu_reloc @ compunit.cu_required_compunits) |> List.map (fun (Compunit i) -> i) let provided compunit = List.filter_map (fun (rel, _pos) -> match rel with | Reloc_setcompunit (Compunit id) -> Some id | _ -> None) compunit.cu_reloc let linkdeps_unit ldeps ~filename compunit = let requires = required compunit in (* [requires] contains pack submodules *) let provides = provided compunit in let Compunit compunit = compunit.cu_name in Linkdeps.add ldeps ~filename ~compunit ~requires ~provides let scan_file ldeps obj_name tolink = let file_name = try Load_path.find obj_name with Not_found -> raise(Error(File_not_found obj_name)) in let ic = open_in_bin file_name in try let buffer = really_input_string ic (String.length cmo_magic_number) in if buffer = cmo_magic_number then begin (* This is a .cmo file. It must be linked in any case. Read the relocation information to see which modules it requires. *) let compunit_pos = input_binary_int ic in (* Go to descriptor *) seek_in ic compunit_pos; let compunit = (input_value ic : compilation_unit) in close_in ic; linkdeps_unit ldeps ~filename:obj_name compunit; Link_object(file_name, compunit) :: tolink end else if buffer = cma_magic_number then begin (* This is an archive file. Each unit contained in it will be linked in only if needed. *) let pos_toc = input_binary_int ic in (* Go to table of contents *) seek_in ic pos_toc; let toc = (input_value ic : library) in close_in ic; add_ccobjs obj_name (Filename.dirname file_name) toc; let required = List.fold_right (fun compunit reqd -> let Compunit name = compunit.cu_name in if compunit.cu_force_link || !Clflags.link_everything || Linkdeps.required ldeps name then begin linkdeps_unit ldeps ~filename:obj_name compunit; compunit :: reqd end else reqd) toc.lib_units [] in Link_archive(file_name, required) :: tolink end else raise(Error(Not_an_object_file file_name)) with End_of_file -> close_in ic; raise(Error(Not_an_object_file file_name)) | x -> close_in ic; raise x (* Second pass: link in the required units *) (* Consistency check between interfaces *) module Consistbl = Consistbl.Make (Misc.Stdlib.String) let crc_interfaces = Consistbl.create () let interfaces = ref ([] : string list) let check_consistency file_name cu = try List.iter (fun (name, crco) -> interfaces := name :: !interfaces; match crco with None -> () | Some crc -> Consistbl.check crc_interfaces name crc file_name) cu.cu_imports with Consistbl.Inconsistency { unit_name = name; inconsistent_source = user; original_source = auth; } -> raise(Error(Inconsistent_import(name, user, auth))) let extract_crc_interfaces () = Consistbl.extract !interfaces crc_interfaces let clear_crc_interfaces () = Consistbl.clear crc_interfaces; interfaces := [] (* Record compilation events *) let debug_info = ref ([] : (int * Instruct.debug_event list * string list) list) (* Link in a compilation unit *) let link_compunit accu output_fun currpos_fun inchan file_name compunit = check_consistency file_name compunit; seek_in inchan compunit.cu_pos; let code_block = Bigarray.Array1.create Bigarray.Char Bigarray.c_layout compunit.cu_codesize in match In_channel.really_input_bigarray inchan code_block 0 compunit.cu_codesize with | None -> raise End_of_file | Some () -> (); Symtable.patch_object code_block compunit.cu_reloc; if !Clflags.debug && compunit.cu_debug > 0 then begin seek_in inchan compunit.cu_debug; let debug_event_list : Instruct.debug_event list = Compression.input_value inchan in let debug_dirs : string list = Compression.input_value inchan in let file_path = Filename.dirname (Location.absolute_path file_name) in let debug_dirs = if List.mem file_path debug_dirs then debug_dirs else file_path :: debug_dirs in debug_info := (currpos_fun(), debug_event_list, debug_dirs) :: !debug_info end; output_fun code_block; let fold_primitive (needs_stdlib, uses_dynlink) name = if !Clflags.link_everything then Symtable.require_primitive name; (needs_stdlib || name = "%standard_library_default", uses_dynlink || name = "caml_reify_bytecode") in List.fold_left fold_primitive accu compunit.cu_primitives (* Link in a .cmo file *) let link_object accu output_fun currpos_fun file_name compunit = In_channel.with_open_bin file_name @@ fun inchan -> try link_compunit accu output_fun currpos_fun inchan file_name compunit with Symtable.Error msg -> raise(Error(Symbol_error(file_name, msg))) (* Link in a .cma file *) let link_archive accu output_fun currpos_fun file_name units_required = In_channel.with_open_bin file_name @@ fun inchan -> List.fold_left (fun accu cu -> let n = Compunit.name cu.cu_name in let name = file_name ^ "(" ^ n ^ ")" in try link_compunit accu output_fun currpos_fun inchan name cu with Symtable.Error msg -> raise(Error(Symbol_error(name, msg)))) accu units_required (* Link in a .cmo or .cma file *) let link_file output_fun currpos_fun accu = function Link_object(file_name, unit) -> link_object accu output_fun currpos_fun file_name unit | Link_archive(file_name, units) -> link_archive accu output_fun currpos_fun file_name units let link_files output_fun currpos_fun = List.fold_left (link_file output_fun currpos_fun) (false, false) (* Output the debugging information *) (* Format is: number of event lists offset of first event list first event list ... offset of last event list last event list *) let output_debug_info oc = output_binary_int oc (List.length !debug_info); List.iter (fun (ofs, evl, debug_dirs) -> output_binary_int oc ofs; output_value oc evl; output_value oc debug_dirs) !debug_info; debug_info := [] (* Transform a file name into an absolute file name *) type launch_method = | Shebang_bin_sh of string | Shebang_runtime | Executable (* See https://www.in-ulm.de/~mascheck/various/shebang/#origin for a deep dive into shebangs. - Whitespace (space or horizontal tab) delimits the interpreter from an optional argument - The path clearly must not contain a linefeed - A maximum length of 125 (128 less the #! and the newline) is picked as a portable maximum (it's actually Linux's prior to kernel v5.1), rather than actually probing the maximum length in configure *) let invalid_for_shebang_line path = let invalid_char = function ' ' | '\t' | '\n' -> true | _ -> false in String.length path > 125 || String.exists invalid_char path let find_bin_sh () = let output_file = Filename.temp_file "caml_bin_sh" "" in let result = try let run command args = let cmd = Filename.quote_command ~stdout:output_file command args in if !Clflags.verbose then Printf.eprintf "+ %s\n" cmd; (Sys.command cmd = 0) in (* While [command -v] and [command -p] are long-standing Posix commands, the ability to combine them as [command -p -v] is actually Posix Issue 7 and so of course Solaris does not support it *) if run "command" ["-p"; "-v"; "sh"] || run "sh" ["-c"; "PATH=\"`getconf PATH`\" command -v sh"] then In_channel.with_open_text output_file input_line else "" with Sys_error _ | End_of_file -> "" in remove_file output_file; result (* Writes the shell script version of the bytecode launcher to outchan *) let write_sh_launcher outchan bin_sh bindir search runtime = let open struct type tag = D | A | E end in let l tag fmt = let output s = if tag = D || tag = A && search <> Config.Absolute || tag = E && search = Config.Absolute_then_search then begin output_string outchan (String.trim s); output_char outchan '\n' end in Printf.ksprintf output fmt in let runtime = Filename.quote runtime in let bin = Filename.quote (Filename.concat bindir "") in let exec = if search = Config.Absolute then runtime else {|"$c"|} in let release = Printf.sprintf "%d.%d" Sys.ocaml_release.major Sys.ocaml_release.minor in (* Each of the three search modes requires a slightly different shell script. However, these shell scripts do have one very useful property: the script for Absolute_then_search adds lines to the script for Search which adds lines to the script for Absolute, but none of them change lines (apart from a trivial tweak to the exec line for the Absolute script). The lines below are laid out to reflect this, with the tag letters D(isable) for the lines in the Absolute script, A(lways) for the lines in Search script and E(nable) for the Absolute_then_search script. If a line is emitted, it is first passed to String.trim, which allows indentation and a column-based layout to be used. The Absolute script just needs to exec the runtime. The two searching modes do a few more calculations and will ultimately exec the contents of $c (which is why exec_arg above is set to the literal string {v "$c" v}). In the script itself: - $r is the name of the runtime ('ocamlrun', 'ocamlrund', etc.) - $d is calculated in the script as $(dirname "$0") - i.e. the directory containing the bytecode executable itself - $c will ultimately be the runtime to exec. If it is empty, then the script displays an error message. In Absolute_then_search, $c will be the first runtime to try (i.e. the runtime in bindir), and the bindir passed must end with a separator (which is ensured by Filename.concat above) The script tries up to three options: - exec $c, if it exists (prefer the runtime in bindir) - exec $d/$r, if it exists (prefer a runtime in the same directory as the bytecode executable) - otherwise try $(command -v "$r") (search PATH for the runtime) If the script fails to find an interpreter, $c will always be empty (since [command -v] will have returned an empty string) and an error message can be displayed. *) l D {|#!%s |} bin_sh; l A {|r=%s |} runtime; l E {|c=%s"$r" |} bin; l E {|if ! test -f "$c"; then |}; l A {| d="$(dirname "$0" 2>/dev/null)" |}; l A {| test -z "$d" || d="${d%%/}/" |}; l A {| c="$(command -v "$d$r")" |}; l A {| test -n "$c" || c="$(command -v "$r")" |}; l E {|fi |}; l A {|if test -z "$c"; then |}; l A {| echo 'This program requires an OCaml %s interpreter'>&2|} release; l A {| echo "$r not found either with $0 or in \$PATH">&2 |}; l A {|else |}; l D {| exec %s "$0" "$@" |} exec; l A {|fi |}; l A {|exit 126 |} (* Writes the executable header to outchan and writes the RNTM section, if needed. Returns a toc_writer (i.e. Bytesections.init_record is always called) *) let write_header outchan = let zinc_runtime_id, write_exe_launcher = let header = let header = "runtime-launch-info" in try Load_path.find header with Not_found -> raise (Error (File_not_found header)) in let data = try In_channel.with_open_bin header In_channel.input_all with Sys_error msg -> raise (Error (Camlheader (msg, header))) in let zinc_runtime_id, offset = if String.length data < 2 then raise (Error (Camlheader ("corrupt header", header))) else if data.[0] = '\000' then None, 1 else let zinc = Misc.RuntimeID.of_zinc_hi (String.sub data 0 2) in if Option.fold ~none:false ~some:Misc.RuntimeID.is_zinc zinc then zinc, 2 else raise (Error (Camlheader ("corrupt header", header))) in let write_exe_header outchan = let len = String.length data in Out_channel.output_substring outchan data offset (len - offset) in zinc_runtime_id, write_exe_header in (* Determine which method will be used for launching the executable: Executable: concatenate the bytecode image to the executable stub Shebang_runtime: #! line with the required runtime Shebang_bin_sh: #! for a shell script calling exec *) let launcher, bindir = match !Clflags.launch_method with | Config.Executable, bindir -> Executable, bindir | Config.Shebang sh, bindir -> Shebang_bin_sh (Option.value ~default:"sh" sh), bindir in let runtime, search = if String.length !Clflags.use_runtime > 0 then (* Do not use BUILD_PATH_PREFIX_MAP mapping for this. *) let runtime = !Clflags.use_runtime in if Filename.is_relative runtime then Filename.concat (Sys.getcwd ()) runtime, Config.Absolute else runtime, Config.Absolute else let runtime = let runtime = "ocamlrun" ^ !Clflags.runtime_variant in let some = Misc.RuntimeID.ocamlrun !Clflags.runtime_variant in Option.fold ~none:runtime ~some zinc_runtime_id in if !Clflags.search_method <> Config.Absolute then runtime, !Clflags.search_method else Filename.concat bindir runtime, Config.Absolute in let launcher = if launcher = Executable then Executable else if search <> Config.Absolute || invalid_for_shebang_line runtime then match launcher with | Shebang_bin_sh sh -> let sh = if sh = "sh" then find_bin_sh () else sh in if sh = "" || invalid_for_shebang_line sh then Executable else Shebang_bin_sh sh | _ -> Executable else Shebang_runtime in (* Write the header *) match launcher with | Shebang_runtime -> assert (search = Config.Absolute); (* Use the runtime directly *) Printf.fprintf outchan "#!%s\n" runtime; Bytesections.init_record outchan | Shebang_bin_sh bin_sh -> (* Use the shebang launcher *) write_sh_launcher outchan bin_sh bindir search runtime; Bytesections.init_record outchan | Executable -> (* Use the executable stub launcher *) write_exe_launcher outchan; (* The runtime name needs recording in RNTM *) let toc_writer = Bytesections.init_record outchan in (* stdlib/header.c determines which mode is needed based on whether the RNTM section contains an embedded NUL character. For Absolute, the path is written verbatim (no extra NUL), otherwise the directory separator just before the basename is effectively turned into a NUL (for Search, there is no dirname, so the string "begins" with a NUL character). *) if search = Absolute then output_string outchan runtime else begin if search = Absolute_then_search then (* Ensure bindir does _not_ end up with a separator *) output_string outchan (Filename.(dirname (concat bindir current_dir_name))); output_char outchan '\000'; output_string outchan runtime end; Bytesections.record toc_writer RNTM; toc_writer (* Create a bytecode executable file *) let link_bytecode ?final_name tolink exec_name standalone = let final_name = Option.value final_name ~default:exec_name in (* Avoid the case where the specified exec output file is the same as one of the objects to be linked *) List.iter (function | Link_object(file_name, _) when file_name = exec_name -> raise (Error (Wrong_object_name exec_name)); | _ -> ()) tolink; (* Remove the output file if it exists to avoid permission problems (PR#8354), but don't risk removing a special file (PR#11302). *) Misc.remove_file exec_name; let outperm = if !Clflags.with_runtime then 0o777 else 0o666 in let outchan = open_out_gen [Open_wronly; Open_trunc; Open_creat; Open_binary] outperm exec_name in Misc.try_finally ~always:(fun () -> close_out outchan) ~exceptionally:(fun () -> remove_file exec_name) (fun () -> let toc_writer = (* Write the header and set the path to the bytecode interpreter *) if standalone && !Clflags.with_runtime then write_header outchan else Bytesections.init_record outchan in (* The bytecode *) let start_code = pos_out outchan in Symtable.init(); clear_crc_interfaces (); let (tocheck, sharedobjs) = let process_dllib ((suffixed, name) as dllib) (tocheck, sharedobjs) = let resolved_name = Dll.extract_dll_name dllib in let partial_name = if suffixed then if String.starts_with ~prefix:"-l" name then (suffixed, "dll" ^ String.sub name 2 (String.length name - 2)) else dllib else (false, resolved_name) in (resolved_name::tocheck, partial_name::sharedobjs) in List.fold_right process_dllib !Clflags.dllibs ([], []) in let check_dlls = standalone && Config.target = Config.host in if check_dlls then begin (* Initialize the DLL machinery *) Dll.init_compile !Clflags.no_std_include; Dll.add_path (Load_path.get_path_list ()); try Dll.open_dlls Dll.For_checking tocheck with Failure reason -> raise(Error(Cannot_open_dll reason)) end; let output_fun buf = Out_channel.output_bigarray outchan buf 0 (Bigarray.Array1.dim buf) and currpos_fun () = pos_out outchan - start_code in (* link_files returns true if any module refers to caml_reify_bytecode, which is used solely by the toplevel and dynlink libraries and is used to control whether we included the CRCS section. *) let needs_stdlib, uses_dynlink = link_files output_fun currpos_fun tolink in if check_dlls then Dll.close_all_dlls(); (* The final STOP instruction *) output_byte outchan Opcodes.opSTOP; output_byte outchan 0; output_byte outchan 0; output_byte outchan 0; Bytesections.record toc_writer CODE; (* DLL stuff *) if standalone then begin (* The extra search path for DLLs *) if !Clflags.dllpaths <> [] then begin output_string outchan (concat_null_terminated !Clflags.dllpaths); Bytesections.record toc_writer DLPT end; (* The names of the DLLs *) if sharedobjs <> [] then begin let output_sharedobj (suffixed, name) = output_char outchan (if suffixed then '-' else ':'); output_string outchan name; output_byte outchan 0 in List.iter output_sharedobj sharedobjs; Bytesections.record toc_writer DLLS end end; (* The names of all primitives *) Symtable.output_primitive_names outchan; Bytesections.record toc_writer PRIM; (* The table of global data *) Emitcode.marshal_to_channel_with_possibly_32bit_compat ~filename:final_name ~kind:"bytecode executable" outchan (Symtable.initial_global_table()); Bytesections.record toc_writer DATA; let standard_library_default = if standalone && needs_stdlib then (* -set-runtime-default *) if !Clflags.standard_library_default = None then Some Config.standard_library_effective else !Clflags.standard_library_default else (* -custom executables don't need OSLD sections - the correct value is already included in the runtime. *) None in begin match standard_library_default with | Some value -> (* OCaml Standard Library Default location *) output_string outchan value; Bytesections.record toc_writer OSLD | None -> () end; begin match Compenv.overridden_runtime_parameters () with | Some ocamlrunparam when standalone -> (* Embedded runtime defaults *) output_string outchan ocamlrunparam; Bytesections.record toc_writer ORUN; | _ -> () end; (* The map of global identifiers *) Symtable.output_global_map outchan; Bytesections.record toc_writer SYMB; (* CRCs for modules *) if uses_dynlink then begin output_value outchan (extract_crc_interfaces()); Bytesections.record toc_writer CRCS end; (* Debug info *) if !Clflags.debug then begin output_debug_info outchan; Bytesections.record toc_writer DBUG end; (* The table of contents and the trailer *) Bytesections.write_toc_and_trailer toc_writer; ) (* Output a string as a C array of unsigned ints *) let output_code_string_counter = ref 0 let output_code_string outchan code = let pos = ref 0 in let len = Bigarray.Array1.dim code in while !pos < len do let c1 = Char.code(Bigarray.Array1.get code !pos) in let c2 = Char.code(Bigarray.Array1.get code (!pos + 1)) in let c3 = Char.code(Bigarray.Array1.get code (!pos + 2)) in let c4 = Char.code(Bigarray.Array1.get code (!pos + 3)) in pos := !pos + 4; Printf.fprintf outchan "0x%02x%02x%02x%02x, " c4 c3 c2 c1; incr output_code_string_counter; if !output_code_string_counter >= 6 then begin output_char outchan '\n'; output_code_string_counter := 0 end done (* Output a string as a C string *) let output_data_string outchan data = let counter = ref 0 in for i = 0 to String.length data - 1 do Printf.fprintf outchan "%d, " (Char.code(data.[i])); incr counter; if !counter >= 12 then begin output_string outchan "\n"; counter := 0 end done (* Output a debug stub *) let output_cds_file outfile = Misc.remove_file outfile; let outchan = open_out_gen [Open_wronly; Open_trunc; Open_creat; Open_binary] 0o777 outfile in Misc.try_finally ~always:(fun () -> close_out outchan) ~exceptionally:(fun () -> remove_file outfile) (fun () -> let toc_writer = Bytesections.init_record outchan in (* The map of global identifiers *) Symtable.output_global_map outchan; Bytesections.record toc_writer SYMB; (* Debug info *) output_debug_info outchan; Bytesections.record toc_writer DBUG; (* The table of contents and the trailer *) Bytesections.write_toc_and_trailer toc_writer; ) (* [c_string_literal_of_string s] returns the C literal string representation of [s], suitable for embedding in a C source file with type [char_os *]. The result includes the quote markers. *) let c_string_literal_of_string s = let b = Buffer.create (String.length s * 2) in let utf16le = Bytes.create 4 in let iter u = match Uchar.to_int u with (* Characters with C escape sequences *) | 000 (* '\0' *) -> Buffer.add_string b "\\0" | 009 (* '\t' *) -> Buffer.add_string b "\\t" | 010 (* '\n' *) -> Buffer.add_string b "\\n" | 013 (* '\r' *) -> Buffer.add_string b "\\r" | 034 (* '\"' *) -> Buffer.add_string b "\\\"" | 092 (* '\\' *) -> Buffer.add_string b "\\\\" (* Most C compilers will have no problem processing UTF-8 in the strings with the characters above converted to their C representations. On Windows, where the string is [wchar_t *], all characters for which iswprint returns 0 are escaped using the extended [\x] notation. *) | c when Config.target_win32 && (c < 32 (* ' ' *) || c >= 127) -> (* Convert u to UTF-16LE, allowing for surrogate pairs *) let len = Bytes.set_utf_16le_uchar utf16le 0 u in for i = 1 to len / 2 do Printf.bprintf b "\\x%04x" (Bytes.get_uint16_le utf16le ((i - 1) * 2)) done | _ -> Buffer.add_utf_8_uchar b u in if Config.target_win32 then Buffer.add_char b 'L'; Buffer.add_char b '"'; Seq.iter iter (String.to_utf_8_seq s); Buffer.add_char b '"'; Buffer.contents b let emit_global_constant outchan name value = let value = Option.fold ~none:"NULL" ~some:c_string_literal_of_string value in Printf.fprintf outchan "const char_os * %s = %s;\n" name value let emit_runtime_standard_library_default outchan = let stdlib = if !Clflags.standard_library_default = None then Some Config.standard_library_effective else !Clflags.standard_library_default in emit_global_constant outchan "caml_runtime_standard_library_default" stdlib (* Output a bytecode executable as a C file *) let link_bytecode_as_c tolink outfile with_main = let outchan = open_out outfile in Misc.try_finally ~always:(fun () -> close_out outchan) ~exceptionally:(fun () -> remove_file outfile) (fun () -> (* The bytecode *) output_string outchan {|#ifdef __cplusplus extern "C" { #endif #define CAML_INTERNALS #define CAMLDLLIMPORT #define CAML_INTERNALS_NO_PRIM_DECLARATIONS #include #include #include #include enum caml_byte_program_mode caml_byte_program_mode = EMBEDDED; static int caml_code[] = { |}; Symtable.init(); clear_crc_interfaces (); let currpos = ref 0 in let output_fun code = output_code_string outchan code; currpos := !currpos + (Bigarray.Array1.dim code) and currpos_fun () = !currpos in let _, uses_dynlink = link_files output_fun currpos_fun tolink in (* The final STOP instruction *) Printf.fprintf outchan "\n0x%x};\n" Opcodes.opSTOP; (* The table of global data *) output_string outchan {| static char caml_data[] = { |}; output_data_string outchan (Marshal.to_string (Symtable.initial_global_table()) []); output_string outchan {| }; |}; (* The sections *) let sections : (string * Obj.t) list = (Bytesections.Name.to_string SYMB, Symtable.data_global_map()) :: if uses_dynlink then [ Bytesections.Name.to_string CRCS, Obj.repr(extract_crc_interfaces()) ] else [] in output_string outchan {| static char caml_sections[] = { |}; output_data_string outchan (Marshal.to_string (Array.of_list sections) []); output_string outchan {| }; |}; emit_global_constant outchan "caml_executable_ocamlrunparam" (Compenv.overridden_runtime_parameters ()); emit_runtime_standard_library_default outchan; (* The table of primitives *) Symtable.output_primitive_table outchan; (* The entry point *) if with_main then begin output_string outchan {| int main_os(int argc, char_os **argv) { caml_startup_code(caml_code, sizeof(caml_code), caml_data, sizeof(caml_data), caml_sections, sizeof(caml_sections), /* pooling */ 0, argv); caml_do_exit(0); return 0; /* not reached */ } |} end else begin output_string outchan {| void caml_startup(char_os ** argv) { caml_startup_code(caml_code, sizeof(caml_code), caml_data, sizeof(caml_data), caml_sections, sizeof(caml_sections), /* pooling */ 0, argv); } value caml_startup_exn(char_os ** argv) { return caml_startup_code_exn(caml_code, sizeof(caml_code), caml_data, sizeof(caml_data), caml_sections, sizeof(caml_sections), /* pooling */ 0, argv); } void caml_startup_pooled(char_os ** argv) { caml_startup_code(caml_code, sizeof(caml_code), caml_data, sizeof(caml_data), caml_sections, sizeof(caml_sections), /* pooling */ 1, argv); } value caml_startup_pooled_exn(char_os ** argv) { return caml_startup_code_exn(caml_code, sizeof(caml_code), caml_data, sizeof(caml_data), caml_sections, sizeof(caml_sections), /* pooling */ 1, argv); } |} end; output_string outchan {| #ifdef __cplusplus } #endif |}; ); if not with_main && !Clflags.debug then output_cds_file ((Filename.chop_extension outfile) ^ ".cds") let runtime_library_name runtime_variant = if runtime_variant = "_shared" && Config.suffixing then Misc.RuntimeID.shared_runtime Sys.Bytecode else "-lcamlrun" ^ runtime_variant (* Build a custom runtime *) let build_custom_runtime prim_name exec_name = let runtime_lib = if not !Clflags.with_runtime then "" else runtime_library_name !Clflags.runtime_variant in let stable_name = if not !Clflags.keep_camlprimc_file then Some "camlprim.c" else None in let prims_obj = Filename.temp_file "camlprim" Config.ext_obj in let result = Ccomp.compile_file ~output:prims_obj ?stable_name prim_name = 0 && Ccomp.call_linker Ccomp.Exe exec_name ([prims_obj] @ List.rev !Clflags.ccobjs @ [runtime_lib]) (Clflags.std_include_flag "-I" ^ " " ^ Config.bytecomp_c_libraries) = 0 in remove_file prims_obj; result let append_bytecode bytecode_name exec_name = let oc = open_out_gen [Open_wronly; Open_append; Open_binary] 0 exec_name in let ic = open_in_bin bytecode_name in copy_file ic oc; close_in ic; close_out oc (* Fix the name of the output file, if the C compiler changes it behind our back. *) let fix_exec_name name = match Sys.os_type with "Win32" | "Cygwin" -> if String.contains name '.' then name else name ^ ".exe" | _ -> name (* Main entry point (build a custom runtime if needed) *) let link objfiles output_name = let objfiles = match !Clflags.nopervasives, !Clflags.output_c_object, !Clflags.output_complete_executable with | true, _, _ -> objfiles | false, true, false -> "stdlib.cma" :: objfiles | _ -> "stdlib.cma" :: objfiles @ ["std_exit.cmo"] in let ldeps = Linkdeps.create ~complete:true in let tolink = List.fold_right (scan_file ldeps) objfiles [] in (match Linkdeps.check ldeps with | None -> () | Some e -> raise (Error (Link_error e))); Clflags.ccobjs := !Clflags.ccobjs @ !lib_ccobjs; (* put user's libs last *) Clflags.all_ccopts := !lib_ccopts @ !Clflags.all_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 output_name true else if not !Clflags.output_c_object then begin let bytecode_name = Filename.temp_file "camlcode" "" in let prim_name = if !Clflags.keep_camlprimc_file then output_name ^ ".camlprim.c" else Filename.temp_file "camlprim" ".c" in Misc.try_finally ~always:(fun () -> remove_file bytecode_name; if not !Clflags.keep_camlprimc_file then remove_file prim_name) (fun () -> link_bytecode ~final_name:output_name tolink bytecode_name false; let poc = open_out prim_name in (* note: builds will not be reproducible if the C code contains macros such as __FILE__. *) output_string poc {|#ifdef __cplusplus extern "C" { #endif #define CAML_INTERNALS #define CAML_INTERNALS_NO_PRIM_DECLARATIONS #include #include enum caml_byte_program_mode caml_byte_program_mode = APPENDED; |}; Symtable.output_primitive_table poc; emit_global_constant poc "caml_executable_ocamlrunparam" (Compenv.overridden_runtime_parameters ()); emit_runtime_standard_library_default poc; output_string poc {| #ifdef __cplusplus } #endif |}; close_out poc; let exec_name = fix_exec_name output_name in if not (build_custom_runtime prim_name exec_name) then raise(Error Custom_runtime); if not !Clflags.make_runtime then append_bytecode bytecode_name exec_name ) end else begin let basename = Filename.remove_extension output_name in let c_file, stable_name = if !Clflags.output_complete_object && not (Filename.check_suffix output_name ".c") then Filename.temp_file "camlobj" ".c", Some "camlobj.c" else begin let f = basename ^ ".c" in if Sys.file_exists f then raise(Error(File_exists f)); f, None end in let obj_file = if !Clflags.output_complete_object then (Filename.chop_extension c_file) ^ Config.ext_obj else basename ^ Config.ext_obj in let temps = ref [] in Misc.try_finally ~always:(fun () -> List.iter remove_file !temps) (fun () -> link_bytecode_as_c tolink c_file !Clflags.output_complete_executable; if !Clflags.output_complete_executable then begin temps := c_file :: !temps; if not (build_custom_runtime c_file output_name) then raise(Error Custom_runtime) end else if not (Filename.check_suffix output_name ".c") then begin temps := c_file :: !temps; if Ccomp.compile_file ~output:obj_file ?stable_name c_file <> 0 then raise(Error Custom_runtime); if not (Filename.check_suffix output_name Config.ext_obj) || !Clflags.output_complete_object then begin temps := obj_file :: !temps; let mode, c_libs = if Filename.check_suffix output_name Config.ext_obj then Ccomp.Partial, "" else Ccomp.MainDll, Config.bytecomp_c_libraries in if not ( let runtime_lib = if not !Clflags.with_runtime then "" else runtime_library_name !Clflags.runtime_variant in Ccomp.call_linker mode output_name ([obj_file] @ List.rev !Clflags.ccobjs @ [runtime_lib]) c_libs = 0 ) then raise (Error Custom_runtime); end end; ) end (* Error report *) open Format_doc module Style = Misc.Style let report_error_doc ppf = function | File_not_found name -> fprintf ppf "Cannot find file %a" Location.Doc.quoted_filename name | Not_an_object_file name -> fprintf ppf "The file %a is not a bytecode object file" Location.Doc.quoted_filename name | Wrong_object_name name -> fprintf ppf "The output file %a has the wrong name. The extension implies\ \ an object file but the link step was requested" Style.inline_code name | Symbol_error(name, err) -> fprintf ppf "Error while linking %a:@ %a" Location.Doc.quoted_filename name Symtable.report_error_doc err | Inconsistent_import(intf, file1, file2) -> fprintf ppf "@[Files %a@ and %a@ \ make inconsistent assumptions over interface %a@]" Location.Doc.quoted_filename file1 Location.Doc.quoted_filename file2 Style.inline_code intf | Custom_runtime -> fprintf ppf "Error while building custom runtime system" | File_exists file -> fprintf ppf "Cannot overwrite existing file %a" Location.Doc.quoted_filename file | Cannot_open_dll file -> fprintf ppf "Error on dynamically loaded library: %a" Location.Doc.filename file | Camlheader (msg, header) -> fprintf ppf "System error while copying file %a: %a" Style.inline_code header Style.inline_code msg | Link_error e -> Linkdeps.report_error_doc ~print_filename:Location.Doc.filename ppf e | Needs_custom_runtime obj_name -> fprintf ppf "%s links with C code, so cannot be linked with -use-prims \ or -use-runtime unless -noautolink is specified" obj_name let () = Location.register_error_of_exn (function | Error err -> Some (Location.error_of_printer_file report_error_doc err) | _ -> None ) let report_error = Format_doc.compat report_error_doc let reset () = lib_ccobjs := []; lib_ccopts := []; lib_dllibs := []; Consistbl.clear crc_interfaces; debug_info := []; output_code_string_counter := 0