ocaml/utils/config.mlp

242 lines
7.9 KiB
Plaintext
Raw Normal View History

#2 "utils/config.mlp"
(**************************************************************************)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
(* The main OCaml version string has moved to ../VERSION *)
let version = Sys.ocaml_version
let standard_library_default = "%%LIBDIR%%"
let standard_library =
try
Sys.getenv "OCAMLLIB"
with Not_found ->
try
Sys.getenv "CAMLLIB"
with Not_found ->
standard_library_default
let ccomp_type = "%%CCOMPTYPE%%"
let c_compiler = "%%CC%%"
let c_output_obj = "%%OUTPUTOBJ%%"
let c_has_debug_prefix_map = %%CC_HAS_DEBUG_PREFIX_MAP%%
let as_has_debug_prefix_map = %%AS_HAS_DEBUG_PREFIX_MAP%%
let ocamlc_cflags = "%%OCAMLC_CFLAGS%%"
let ocamlc_cppflags = "%%OCAMLC_CPPFLAGS%%"
(* #7678: ocamlopt uses these only to compile .c files, and the behaviour for
the two drivers should be identical. *)
let ocamlopt_cflags = "%%OCAMLC_CFLAGS%%"
let ocamlopt_cppflags = "%%OCAMLOPT_CPPFLAGS%%"
let bytecomp_c_libraries = "%%BYTECCLIBS%%"
(* bytecomp_c_compiler and native_c_compiler have been supported for a
long time and are retained for backwards compatibility.
For programs that don't need compatibility with older OCaml releases
the recommended approach is to use the constituent variables
c_compiler, ocamlc_cflags, ocamlc_cppflags etc., directly.
*)
let bytecomp_c_compiler =
c_compiler ^ " " ^ ocamlc_cflags ^ " " ^ ocamlc_cppflags
let native_c_compiler =
c_compiler ^ " " ^ ocamlopt_cflags ^ " " ^ ocamlopt_cppflags
let native_c_libraries = "%%NATIVECCLIBS%%"
let native_pack_linker = "%%PACKLD%%"
let ranlib = "%%RANLIBCMD%%"
let ar = "%%ARCMD%%"
let mkdll, mkexe, mkmaindll =
(* @@DRA Cygwin - but only if shared libraries are enabled, which we
should be able to detect? *)
if Sys.os_type = "Win32" then
try
let flexlink =
let flexlink = Sys.getenv "OCAML_FLEXLINK" in
let f i =
let c = flexlink.[i] in
if c = '/' then '\\' else c in
(String.init (String.length flexlink) f) ^ " %%FLEXLINK_FLAGS%%" in
flexlink,
Unicode support for the Windows runtime (#1200) * Add support code * Explicitly reference ANSI Windows APIs * Adapt Sys.is_directory * Adapt ocamlrun * Add Changes entry * Add testsuite * Adapt Unix.open_process{_in,_out,_full,}, Unix.create_process{_env,} * Adapt headernt.c * Adapt Pervasives.open_{in,out}, Filename.temp_file, etc. * Adapt Sys.file_exists * Adapt Sys.remove * Adapt Sys.chdir * Adapt Sys.getcwd * Adapt Sys.getenv * Adapt Sys.command * Adapt Sys.readdir * Adapt CPLUGINS * Remove use of FormatMessageA, CreateFileA * Adapt Unix.mkdir * Adapt Unix.openfile * Adapt Unix.readlink * Adapt Unix.rename * Adapt Unix.{LargeFile,}.{l,}stat * Adapt Unix.system * Adapt Unix.{open,read}dir * Adapt Unix.link * Adapt Unix.symlink * Adapt Unix.getcwd * Adapt Unix.rmdir * Adapt Unix.utimes * Adapt Unix.unlink * Adapt Unix.chdir * Adapt Unix.chmod * Adapt Unix.{execv,execve,execvp,execvpe} * Compile with -DUNICODE -D_UNICODE under Windows * Add configure-time switch, Config.windows_unicode * Adapt Unix.putenv * Re-implement Unix.environment using GetEnvironmentStrings() * Use Unicode-aware flexdll * Adapt Unix.environment * AppVeyor: bootstrap flexdll * Adapt tests/embedded/cmmain.c * Adapt tests/lib-dynlink-csharp/entry.c * Remove exec tests * Fixup * Pass -municode to MinGW compiler * Try to fix tests/embedded * Adapt Sys.rename * Correct Changes entry * Makefile.several: use $(O) and $(NATIVECODE_ONLY) * Display => skipped correctly for tests/win-unicode * Add missing casts to execv* calls It's not clear why these aren't necessary for with char, but they are necessary with wchar_t on GCC (but not MSVC). * Missing header in systhreads (Win32 only) * Revert "Pass -municode to MinGW compiler" This reverts commit a4ce7fb319c429068a5b9d1ab14a2cc3969c355f. * Revert "Try to fix tests/embedded" This reverts commit 5197d8922295b7b339b970ec3189374aa15de4b8. * Revert "Remove exec tests" This reverts commit 306ccef2e79eca5b38ecfa285b912c7bcf3e9f52. * Don't pass $(LDFLAGS) when build ocamlc.opt It's already included via CC anyway, and it causes Unicode problems for Winodws (because the linker options need to be prefixed "-link" to go via flexlink). * Use wmain on Windows for ocamlrun * Build Unicode applications on Windows * Use wmain in headernt.c * Minor correction to win-unicode Makefile * Switch submodule to FlexDLL 0.36 * Build ocamlyacc as an ANSI application * Revert "Fixup" This reverts commit 500bd6b575ffd6c5b71c6953e55d740f0b090185. * Fix casts for execvp/execve * Remove tabs from test code * Fix Changes entry * shell32.lib is no longer necessary * Free allocated string * Changes: signal breaking change * Disable exec_tests * Protect with CAML_INTERNALS
2017-09-18 08:41:29 -07:00
flexlink ^ " -exe%%FLEXLINK_LDFLAGS%%",
flexlink ^ " -maindll"
with Not_found ->
"%%MKDLL%%", "%%MKEXE%%", "%%MKMAINDLL%%"
else
"%%MKDLL%%", "%%MKEXE%%", "%%MKMAINDLL%%"
let flambda = %%FLAMBDA%%
let with_flambda_invariants = %%WITH_FLAMBDA_INVARIANTS%%
let safe_string = %%FORCE_SAFE_STRING%%
let default_safe_string = %%DEFAULT_SAFE_STRING%%
Unicode support for the Windows runtime (#1200) * Add support code * Explicitly reference ANSI Windows APIs * Adapt Sys.is_directory * Adapt ocamlrun * Add Changes entry * Add testsuite * Adapt Unix.open_process{_in,_out,_full,}, Unix.create_process{_env,} * Adapt headernt.c * Adapt Pervasives.open_{in,out}, Filename.temp_file, etc. * Adapt Sys.file_exists * Adapt Sys.remove * Adapt Sys.chdir * Adapt Sys.getcwd * Adapt Sys.getenv * Adapt Sys.command * Adapt Sys.readdir * Adapt CPLUGINS * Remove use of FormatMessageA, CreateFileA * Adapt Unix.mkdir * Adapt Unix.openfile * Adapt Unix.readlink * Adapt Unix.rename * Adapt Unix.{LargeFile,}.{l,}stat * Adapt Unix.system * Adapt Unix.{open,read}dir * Adapt Unix.link * Adapt Unix.symlink * Adapt Unix.getcwd * Adapt Unix.rmdir * Adapt Unix.utimes * Adapt Unix.unlink * Adapt Unix.chdir * Adapt Unix.chmod * Adapt Unix.{execv,execve,execvp,execvpe} * Compile with -DUNICODE -D_UNICODE under Windows * Add configure-time switch, Config.windows_unicode * Adapt Unix.putenv * Re-implement Unix.environment using GetEnvironmentStrings() * Use Unicode-aware flexdll * Adapt Unix.environment * AppVeyor: bootstrap flexdll * Adapt tests/embedded/cmmain.c * Adapt tests/lib-dynlink-csharp/entry.c * Remove exec tests * Fixup * Pass -municode to MinGW compiler * Try to fix tests/embedded * Adapt Sys.rename * Correct Changes entry * Makefile.several: use $(O) and $(NATIVECODE_ONLY) * Display => skipped correctly for tests/win-unicode * Add missing casts to execv* calls It's not clear why these aren't necessary for with char, but they are necessary with wchar_t on GCC (but not MSVC). * Missing header in systhreads (Win32 only) * Revert "Pass -municode to MinGW compiler" This reverts commit a4ce7fb319c429068a5b9d1ab14a2cc3969c355f. * Revert "Try to fix tests/embedded" This reverts commit 5197d8922295b7b339b970ec3189374aa15de4b8. * Revert "Remove exec tests" This reverts commit 306ccef2e79eca5b38ecfa285b912c7bcf3e9f52. * Don't pass $(LDFLAGS) when build ocamlc.opt It's already included via CC anyway, and it causes Unicode problems for Winodws (because the linker options need to be prefixed "-link" to go via flexlink). * Use wmain on Windows for ocamlrun * Build Unicode applications on Windows * Use wmain in headernt.c * Minor correction to win-unicode Makefile * Switch submodule to FlexDLL 0.36 * Build ocamlyacc as an ANSI application * Revert "Fixup" This reverts commit 500bd6b575ffd6c5b71c6953e55d740f0b090185. * Fix casts for execvp/execve * Remove tabs from test code * Fix Changes entry * shell32.lib is no longer necessary * Free allocated string * Changes: signal breaking change * Disable exec_tests * Protect with CAML_INTERNALS
2017-09-18 08:41:29 -07:00
let windows_unicode = %%WINDOWS_UNICODE%% != 0
let supports_shared_libraries = %%SUPPORTS_SHARED_LIBRARIES%%
let flat_float_array = %%FLAT_FLOAT_ARRAY%%
let function_sections = %%FUNCTION_SECTIONS%%
let afl_instrument = %%AFL_INSTRUMENT%%
let exec_magic_number = "Caml1999X029"
(* exec_magic_number is duplicated in runtime/caml/exec.h *)
and cmi_magic_number = "Caml1999I029"
and cmo_magic_number = "Caml1999O029"
and cma_magic_number = "Caml1999A029"
and cmx_magic_number =
if flambda then
"Caml1999y029"
else
"Caml1999Y029"
and cmxa_magic_number =
if flambda then
"Caml1999z029"
else
"Caml1999Z029"
and ast_impl_magic_number = "Caml1999M029"
and ast_intf_magic_number = "Caml1999N029"
and cmxs_magic_number = "Caml1999D029"
and cmt_magic_number = "Caml1999T029"
and linear_magic_number = "Caml1999L029"
let interface_suffix = ref ".mli"
let max_tag = 245
(* This is normally the same as in obj.ml, but we have to define it
separately because it can differ when we're in the middle of a
bootstrapping phase. *)
let lazy_tag = 246
let max_young_wosize = 256
let stack_threshold = 256 (* see runtime/caml/config.h *)
let stack_safety_margin = 60
let architecture = "%%ARCH%%"
let model = "%%MODEL%%"
let system = "%%SYSTEM%%"
let asm = "%%ASM%%"
let asm_cfi_supported = %%ASM_CFI_SUPPORTED%%
let with_frame_pointers = %%WITH_FRAME_POINTERS%%
let profinfo = %%WITH_PROFINFO%%
let profinfo_width = %%PROFINFO_WIDTH%%
let ext_exe = "%%EXE%%"
let ext_obj = "%%EXT_OBJ%%"
let ext_asm = "%%EXT_ASM%%"
let ext_lib = "%%EXT_LIB%%"
let ext_dll = "%%EXT_DLL%%"
let host = "%%HOST%%"
let target = "%%TARGET%%"
let default_executable_name =
match Sys.os_type with
"Unix" -> "a.out"
| "Win32" | "Cygwin" -> "camlprog.exe"
| _ -> "camlprog"
let systhread_supported = %%SYSTHREAD_SUPPORT%%;;
let flexdll_dirs = [%%FLEXDLL_DIR%%];;
ocamlc -config: new -config-var option to print specific configuration variables The proposed behavior of `-config-var s` is as follows: - if `s` is an existing configuration variable, print its value as a string and exit with a success return value (0) - if `s` is not an existing configuration variable, print nothing and exit with a failure return value (non-0) Note that we do not print a newline after the value of the configuration variable. In particular, if the value is an empty string, the output is undistinguishable from the output for non-existing variables, the return value has to be considered instead. The following alternative behaviors were considered: - We could print a newline after the configuration value, which would let users distinguish empty values from non-existing variables by counting the lines of output, and would also be more pleasant for users invoking the option from the command-line. However, the way bash works on Windows means that $(ocamlc -config-var foo) would keep a trailing \r in its output, and portable scripts would have to use $(ocamlc -config-var foo | tr -d '\r') instead, which is a pain. (This issue was pointed out by David Allsopp) - We could print a message on the error output if the configuration variable does not exist. This is clearer to a human user, but it is annoying for scripts if they forget to silence the error output and get their output mixed with our error messages. The main use of this new feature is for scripting purposes.
2017-10-14 09:46:58 -07:00
type configuration_value =
| String of string
| Int of int
| Bool of bool
let configuration_variables =
let p x v = (x, String v) in
let p_int x v = (x, Int v) in
let p_bool x v = (x, Bool v) in
[
p "version" version;
p "standard_library_default" standard_library_default;
p "standard_library" standard_library;
p "ccomp_type" ccomp_type;
p "c_compiler" c_compiler;
p "ocamlc_cflags" ocamlc_cflags;
p "ocamlc_cppflags" ocamlc_cppflags;
p "ocamlopt_cflags" ocamlopt_cflags;
p "ocamlopt_cppflags" ocamlopt_cppflags;
p "bytecomp_c_compiler" bytecomp_c_compiler;
p "native_c_compiler" native_c_compiler;
p "bytecomp_c_libraries" bytecomp_c_libraries;
p "native_c_libraries" native_c_libraries;
p "native_pack_linker" native_pack_linker;
p "ranlib" ranlib;
p "architecture" architecture;
p "model" model;
p_int "int_size" Sys.int_size;
p_int "word_size" Sys.word_size;
p "system" system;
p "asm" asm;
p_bool "asm_cfi_supported" asm_cfi_supported;
p_bool "with_frame_pointers" with_frame_pointers;
p "ext_exe" ext_exe;
p "ext_obj" ext_obj;
p "ext_asm" ext_asm;
p "ext_lib" ext_lib;
p "ext_dll" ext_dll;
p "os_type" Sys.os_type;
p "default_executable_name" default_executable_name;
p_bool "systhread_supported" systhread_supported;
p "host" host;
p "target" target;
p_bool "flambda" flambda;
p_bool "safe_string" safe_string;
p_bool "default_safe_string" default_safe_string;
p_bool "flat_float_array" flat_float_array;
p_bool "function_sections" function_sections;
p_bool "afl_instrument" afl_instrument;
Unicode support for the Windows runtime (#1200) * Add support code * Explicitly reference ANSI Windows APIs * Adapt Sys.is_directory * Adapt ocamlrun * Add Changes entry * Add testsuite * Adapt Unix.open_process{_in,_out,_full,}, Unix.create_process{_env,} * Adapt headernt.c * Adapt Pervasives.open_{in,out}, Filename.temp_file, etc. * Adapt Sys.file_exists * Adapt Sys.remove * Adapt Sys.chdir * Adapt Sys.getcwd * Adapt Sys.getenv * Adapt Sys.command * Adapt Sys.readdir * Adapt CPLUGINS * Remove use of FormatMessageA, CreateFileA * Adapt Unix.mkdir * Adapt Unix.openfile * Adapt Unix.readlink * Adapt Unix.rename * Adapt Unix.{LargeFile,}.{l,}stat * Adapt Unix.system * Adapt Unix.{open,read}dir * Adapt Unix.link * Adapt Unix.symlink * Adapt Unix.getcwd * Adapt Unix.rmdir * Adapt Unix.utimes * Adapt Unix.unlink * Adapt Unix.chdir * Adapt Unix.chmod * Adapt Unix.{execv,execve,execvp,execvpe} * Compile with -DUNICODE -D_UNICODE under Windows * Add configure-time switch, Config.windows_unicode * Adapt Unix.putenv * Re-implement Unix.environment using GetEnvironmentStrings() * Use Unicode-aware flexdll * Adapt Unix.environment * AppVeyor: bootstrap flexdll * Adapt tests/embedded/cmmain.c * Adapt tests/lib-dynlink-csharp/entry.c * Remove exec tests * Fixup * Pass -municode to MinGW compiler * Try to fix tests/embedded * Adapt Sys.rename * Correct Changes entry * Makefile.several: use $(O) and $(NATIVECODE_ONLY) * Display => skipped correctly for tests/win-unicode * Add missing casts to execv* calls It's not clear why these aren't necessary for with char, but they are necessary with wchar_t on GCC (but not MSVC). * Missing header in systhreads (Win32 only) * Revert "Pass -municode to MinGW compiler" This reverts commit a4ce7fb319c429068a5b9d1ab14a2cc3969c355f. * Revert "Try to fix tests/embedded" This reverts commit 5197d8922295b7b339b970ec3189374aa15de4b8. * Revert "Remove exec tests" This reverts commit 306ccef2e79eca5b38ecfa285b912c7bcf3e9f52. * Don't pass $(LDFLAGS) when build ocamlc.opt It's already included via CC anyway, and it causes Unicode problems for Winodws (because the linker options need to be prefixed "-link" to go via flexlink). * Use wmain on Windows for ocamlrun * Build Unicode applications on Windows * Use wmain in headernt.c * Minor correction to win-unicode Makefile * Switch submodule to FlexDLL 0.36 * Build ocamlyacc as an ANSI application * Revert "Fixup" This reverts commit 500bd6b575ffd6c5b71c6953e55d740f0b090185. * Fix casts for execvp/execve * Remove tabs from test code * Fix Changes entry * shell32.lib is no longer necessary * Free allocated string * Changes: signal breaking change * Disable exec_tests * Protect with CAML_INTERNALS
2017-09-18 08:41:29 -07:00
p_bool "windows_unicode" windows_unicode;
p_bool "supports_shared_libraries" supports_shared_libraries;
p "exec_magic_number" exec_magic_number;
p "cmi_magic_number" cmi_magic_number;
p "cmo_magic_number" cmo_magic_number;
p "cma_magic_number" cma_magic_number;
p "cmx_magic_number" cmx_magic_number;
p "cmxa_magic_number" cmxa_magic_number;
p "ast_impl_magic_number" ast_impl_magic_number;
p "ast_intf_magic_number" ast_intf_magic_number;
p "cmxs_magic_number" cmxs_magic_number;
p "cmt_magic_number" cmt_magic_number;
p "linear_magic_number" linear_magic_number;
ocamlc -config: new -config-var option to print specific configuration variables The proposed behavior of `-config-var s` is as follows: - if `s` is an existing configuration variable, print its value as a string and exit with a success return value (0) - if `s` is not an existing configuration variable, print nothing and exit with a failure return value (non-0) Note that we do not print a newline after the value of the configuration variable. In particular, if the value is an empty string, the output is undistinguishable from the output for non-existing variables, the return value has to be considered instead. The following alternative behaviors were considered: - We could print a newline after the configuration value, which would let users distinguish empty values from non-existing variables by counting the lines of output, and would also be more pleasant for users invoking the option from the command-line. However, the way bash works on Windows means that $(ocamlc -config-var foo) would keep a trailing \r in its output, and portable scripts would have to use $(ocamlc -config-var foo | tr -d '\r') instead, which is a pain. (This issue was pointed out by David Allsopp) - We could print a message on the error output if the configuration variable does not exist. This is clearer to a human user, but it is annoying for scripts if they forget to silence the error output and get their output mixed with our error messages. The main use of this new feature is for scripting purposes.
2017-10-14 09:46:58 -07:00
]
let print_config_value oc = function
| String s ->
Printf.fprintf oc "%s" s
| Int n ->
Printf.fprintf oc "%d" n
| Bool p ->
Printf.fprintf oc "%B" p
ocamlc -config: new -config-var option to print specific configuration variables The proposed behavior of `-config-var s` is as follows: - if `s` is an existing configuration variable, print its value as a string and exit with a success return value (0) - if `s` is not an existing configuration variable, print nothing and exit with a failure return value (non-0) Note that we do not print a newline after the value of the configuration variable. In particular, if the value is an empty string, the output is undistinguishable from the output for non-existing variables, the return value has to be considered instead. The following alternative behaviors were considered: - We could print a newline after the configuration value, which would let users distinguish empty values from non-existing variables by counting the lines of output, and would also be more pleasant for users invoking the option from the command-line. However, the way bash works on Windows means that $(ocamlc -config-var foo) would keep a trailing \r in its output, and portable scripts would have to use $(ocamlc -config-var foo | tr -d '\r') instead, which is a pain. (This issue was pointed out by David Allsopp) - We could print a message on the error output if the configuration variable does not exist. This is clearer to a human user, but it is annoying for scripts if they forget to silence the error output and get their output mixed with our error messages. The main use of this new feature is for scripting purposes.
2017-10-14 09:46:58 -07:00
let print_config oc =
let print (x, v) =
Printf.fprintf oc "%s: %a\n" x print_config_value v in
List.iter print configuration_variables;
flush oc;
;;
ocamlc -config: new -config-var option to print specific configuration variables The proposed behavior of `-config-var s` is as follows: - if `s` is an existing configuration variable, print its value as a string and exit with a success return value (0) - if `s` is not an existing configuration variable, print nothing and exit with a failure return value (non-0) Note that we do not print a newline after the value of the configuration variable. In particular, if the value is an empty string, the output is undistinguishable from the output for non-existing variables, the return value has to be considered instead. The following alternative behaviors were considered: - We could print a newline after the configuration value, which would let users distinguish empty values from non-existing variables by counting the lines of output, and would also be more pleasant for users invoking the option from the command-line. However, the way bash works on Windows means that $(ocamlc -config-var foo) would keep a trailing \r in its output, and portable scripts would have to use $(ocamlc -config-var foo | tr -d '\r') instead, which is a pain. (This issue was pointed out by David Allsopp) - We could print a message on the error output if the configuration variable does not exist. This is clearer to a human user, but it is annoying for scripts if they forget to silence the error output and get their output mixed with our error messages. The main use of this new feature is for scripting purposes.
2017-10-14 09:46:58 -07:00
let config_var x =
match List.assoc_opt x configuration_variables with
| None -> None
| Some v ->
let s = match v with
| String s -> s
2018-08-30 10:15:32 -07:00
| Int n -> Int.to_string n
ocamlc -config: new -config-var option to print specific configuration variables The proposed behavior of `-config-var s` is as follows: - if `s` is an existing configuration variable, print its value as a string and exit with a success return value (0) - if `s` is not an existing configuration variable, print nothing and exit with a failure return value (non-0) Note that we do not print a newline after the value of the configuration variable. In particular, if the value is an empty string, the output is undistinguishable from the output for non-existing variables, the return value has to be considered instead. The following alternative behaviors were considered: - We could print a newline after the configuration value, which would let users distinguish empty values from non-existing variables by counting the lines of output, and would also be more pleasant for users invoking the option from the command-line. However, the way bash works on Windows means that $(ocamlc -config-var foo) would keep a trailing \r in its output, and portable scripts would have to use $(ocamlc -config-var foo | tr -d '\r') instead, which is a pain. (This issue was pointed out by David Allsopp) - We could print a message on the error output if the configuration variable does not exist. This is clearer to a human user, but it is annoying for scripts if they forget to silence the error output and get their output mixed with our error messages. The main use of this new feature is for scripting purposes.
2017-10-14 09:46:58 -07:00
| Bool b -> string_of_bool b
in
Some s
let merlin = false