diff options
-rw-r--r-- | Changes | 1 | ||||
-rwxr-xr-x | boot/ocamlc | bin | 1388354 -> 1390682 bytes | |||
-rwxr-xr-x | boot/ocamldep | bin | 342777 -> 343283 bytes | |||
-rw-r--r-- | driver/main.ml | 48 | ||||
-rw-r--r-- | driver/optmain.ml | 50 | ||||
-rw-r--r-- | utils/misc.ml | 19 | ||||
-rw-r--r-- | utils/misc.mli | 3 |
7 files changed, 114 insertions, 7 deletions
@@ -34,6 +34,7 @@ Compilers: * warning 3 is extended to warn about other deprecated features: - ISO-latin1 characters in identifiers - uses of the (&) and (or) operators instead of (&&) and (||) +- Experimental OCAMLCOMPPARAM for ocamlc and ocamlopt Standard library: - PR#5986: new flag Marshal.Compat_32 for the serialization functions diff --git a/boot/ocamlc b/boot/ocamlc Binary files differindex dd9d27407..dc64584db 100755 --- a/boot/ocamlc +++ b/boot/ocamlc diff --git a/boot/ocamldep b/boot/ocamldep Binary files differindex c5afc26b8..a889c5cb7 100755 --- a/boot/ocamldep +++ b/boot/ocamldep diff --git a/driver/main.ml b/driver/main.ml index e9aef82ff..93f6d2e63 100644 --- a/driver/main.ml +++ b/driver/main.ml @@ -71,14 +71,55 @@ let print_version_string () = let print_standard_library () = print_string Config.standard_library; print_newline(); exit 0 +let readenv () = (* A copy is in optmain.ml *) + try + let s = Sys.getenv "OCAMLCOMPPARAM" in + List.iter (fun s -> + match Misc.split s '=' with +(* debugging *) + | [ "g" ] + | [ "g"; "1" ] -> Clflags.debug := true + | [ "g"; "0" ] -> Clflags.debug := false +(* profiling *) + | [ "p" ] + | [ "p"; "1" ] -> Clflags.gprofile := true + | [ "p"; "0" ] -> Clflags.gprofile := false +(* sources *) + | [ "s" ] + | [ "s"; "1" ] -> + Clflags.keep_asm_file := true; + Clflags.keep_startup_file := true + | [ "s"; "0" ] -> + Clflags.keep_asm_file := false; + Clflags.keep_startup_file := false +(* warn-errors *) + | [ "we" ] -> Warnings.parse_options true "A" + | [ "we"; warnings ] -> Warnings.parse_options true warnings +(* warnings *) + | [ "w" ] -> Warnings.parse_options false "A" + | [ "w"; warnings ] -> Warnings.parse_options false warnings +(* warn-errors *) + | [ "wwe" ] -> + Warnings.parse_options false "A"; + Warnings.parse_options true "A" + | [ "wwe"; warnings ] -> + Warnings.parse_options false warnings; + Warnings.parse_options true warnings + | _ -> () + ) (Misc.split s ';') + with Not_found -> () + let usage = "Usage: ocamlc <options> <files>\nOptions are:" let ppf = Format.err_formatter (* Error messages to standard error formatter *) -let anonymous = process_file ppf;; -let impl = process_implementation_file ppf;; -let intf = process_interface_file ppf;; +let anonymous filename = + readenv(); process_file ppf filename;; +let impl filename = + readenv(); process_implementation_file ppf filename;; +let intf filename = + readenv(); process_interface_file ppf filename;; let show_config () = Config.print_config stdout; @@ -164,6 +205,7 @@ let default_output = function let main () = try Arg.parse Options.list anonymous usage; + readenv (); if List.length (List.filter (fun x -> !x) [make_archive;make_package;compile_only;output_c_object]) diff --git a/driver/optmain.ml b/driver/optmain.ml index 13b6000c7..d2b0d7164 100644 --- a/driver/optmain.ml +++ b/driver/optmain.ml @@ -83,12 +83,55 @@ let default_output = function | Some s -> s | None -> Config.default_executable_name +let readenv () = (* A copy is in main.ml *) + try + let s = Sys.getenv "OCAMLCOMPPARAM" in + List.iter (fun s -> + match Misc.split s '=' with +(* debugging *) + | [ "g" ] + | [ "g"; "1" ] -> Clflags.debug := true + | [ "g"; "0" ] -> Clflags.debug := false +(* profiling *) + | [ "p" ] + | [ "p"; "1" ] -> Clflags.gprofile := true + | [ "p"; "0" ] -> Clflags.gprofile := false +(* sources *) + | [ "s" ] + | [ "s"; "1" ] -> + Clflags.keep_asm_file := true; + Clflags.keep_startup_file := true + | [ "s"; "0" ] -> + Clflags.keep_asm_file := false; + Clflags.keep_startup_file := false +(* warn-errors *) + | [ "we" ] -> Warnings.parse_options true "A" + | [ "we"; warnings ] -> Warnings.parse_options true warnings +(* warnings *) + | [ "w" ] -> Warnings.parse_options false "A" + | [ "w"; warnings ] -> Warnings.parse_options false warnings +(* warn-errors *) + | [ "wwe" ] -> + Warnings.parse_options false "A"; + Warnings.parse_options true "A" + | [ "wwe"; warnings ] -> + Warnings.parse_options false warnings; + Warnings.parse_options true warnings + | _ -> () + ) (Misc.split s ';') + with Not_found -> () + let usage = "Usage: ocamlopt <options> <files>\nOptions are:" +let ppf = Format.err_formatter + (* Error messages to standard error formatter *) -let anonymous = process_file Format.err_formatter;; -let impl = process_implementation_file Format.err_formatter;; -let intf = process_interface_file Format.err_formatter;; +let anonymous filename = + readenv(); process_file ppf filename;; +let impl filename = + readenv(); process_implementation_file ppf filename;; +let intf filename = + readenv(); process_interface_file ppf filename;; let show_config () = Config.print_config stdout; @@ -178,6 +221,7 @@ let main () = let ppf = Format.err_formatter in try Arg.parse (Arch.command_line_options @ Options.list) anonymous usage; + readenv (); if List.length (List.filter (fun x -> !x) [make_package; make_archive; shared; diff --git a/utils/misc.ml b/utils/misc.ml index 6060b3627..f38f9d3ce 100644 --- a/utils/misc.ml +++ b/utils/misc.ml @@ -271,7 +271,7 @@ end let edit_distance a b cutoff = let la, lb = String.length a, String.length b in - let cutoff = + let cutoff = (* using max_int for cutoff would cause overflows in (i + cutoff + 1); we bring it back to the (max la lb) worstcase *) min (max la lb) cutoff in @@ -313,3 +313,20 @@ let edit_distance a b cutoff = then None else Some result end + + +(* split a string [s] at every char [c], and return the list of sub-strings *) +let split s c = + let len = String.length s in + let rec iter pos to_rev = + if pos = len then List.rev ("" :: to_rev) else + match try + Some ( String.index_from s pos c ) + with Not_found -> None + with + Some pos2 -> + if pos2 = pos then iter (pos+1) ("" :: to_rev) else + iter (pos2+1) ((String.sub s pos (pos2-pos)) :: to_rev) + | None -> List.rev ( String.sub s pos (len-pos) :: to_rev ) + in + iter 0 [] diff --git a/utils/misc.mli b/utils/misc.mli index ac122e30c..deb4588cd 100644 --- a/utils/misc.mli +++ b/utils/misc.mli @@ -122,6 +122,9 @@ val snd4: 'a * 'b * 'c * 'd -> 'b val thd4: 'a * 'b * 'c * 'd -> 'c val for4: 'a * 'b * 'c * 'd -> 'd +(* split a string [s] at every char [c], and return the list of sub-strings *) +val split : string -> char -> string list + module LongString : sig type t = string array |