diff --git a/CHANGES b/CHANGES index 25b3de9..87f8293 100644 --- a/CHANGES +++ b/CHANGES @@ -1,5 +1,6 @@ Next version - GPR#103: Delete objects from C files compiled by flexlink (David Allsopp, report by Xavier Leroy) +- GPR#85: Split multiple arguments passed with a single -Wl (David Allsopp) Version 0.41 - GPR#98: Eliminate Warning 6 compiling coff.ml (David Allsopp) diff --git a/Compat.ml.in b/Compat.ml.in new file mode 100644 index 0000000..2a79c5b --- /dev/null +++ b/Compat.ml.in @@ -0,0 +1,133 @@ +(************************************************************************) +(* FlexDLL *) +(* Alain Frisch *) +(* *) +(* Copyright 2007 Institut National de Recherche en Informatique et *) +(* en Automatique. *) +(************************************************************************) + +(* Compatibility shims. Each line is prefixed with the compiler at which the + line ceases to be necessary. A function introduced in OCaml 4.01, therefore, + is prefixed with "401:" *) + +405:module Arg = struct +405: include Arg +405: +405: let trim_cr s = +405: let len = String.length s in +405: if len > 0 && String.get s (len - 1) = '\r' then +405: String.sub s 0 (len - 1) +405: else +405: s +405: +405: let read_aux trim sep file = +405: let ic = open_in_bin file in +405: let buf = Buffer.create 200 in +405: let words = ref [] in +405: let stash () = +405: let word = Buffer.contents buf in +405: let word = if trim then trim_cr word else word in +405: words := word :: !words; +405: Buffer.clear buf +405: in +405: begin +405: try while true do +405: let c = input_char ic in +405: if c = sep then stash () else Buffer.add_char buf c +405: done +405: with End_of_file -> () +405: end; +405: if Buffer.length buf > 0 then stash (); +405: close_in ic; +405: Array.of_list (List.rev !words) +405: +405: let read_arg = read_aux true '\n' +405: +405: let read_arg0 = read_aux false '\x00' +405: +405:end + +403:module Uchar = struct +403: let unsafe_of_int c = c +403: +403: let to_int c = c +403:end + +406:module Buffer = struct +406: include Buffer +406: +402: let to_bytes = contents +402: +406: let add_utf_16le_uchar b u = match Uchar.to_int u with +406: | u when u < 0 -> assert false +406: | u when u <= 0xFFFF -> +406: add_char b (Char.unsafe_chr (u land 0xFF)); +406: add_char b (Char.unsafe_chr (u lsr 8)) +406: | u when u <= 0x10FFFF -> +406: let u' = u - 0x10000 in +406: let hi = 0xD800 lor (u' lsr 10) in +406: let lo = 0xDC00 lor (u' land 0x3FF) in +406: add_char b (Char.unsafe_chr (hi land 0xFF)); +406: add_char b (Char.unsafe_chr (hi lsr 8)); +406: add_char b (Char.unsafe_chr (lo land 0xFF)); +406: add_char b (Char.unsafe_chr (lo lsr 8)) +406: | _ -> assert false +406:end + +402:module Bytes = struct +402: include String +402: +402: let blit_string = blit +402: let sub_string = sub +402: let of_string x = x +402: let to_string x = x +402: let cat = (^) +402:end + +403:module Char = struct +403: include Char +403: +403: let lowercase_ascii c = +403: if (c >= 'A' && c <= 'Z') +403: then unsafe_chr(code c + 32) +403: else c +403: +403: let uppercase_ascii c = +403: if (c >= 'a' && c <= 'z') +403: then unsafe_chr(code c - 32) +403: else c +403:end + +407:module Stdlib = Pervasives + +404:module String = struct +404: include String +402: +402: let init n f = +402: let s = create n in +402: for i = 0 to n - 1 do +402: unsafe_set s i (f i) +402: done; +402: s +403: +403: let lowercase_ascii s = +403: init (length s) (fun i -> Char.lowercase_ascii (unsafe_get s i)) +403: let uppercase_ascii s = +403: init (length s) (fun i -> Char.uppercase_ascii (unsafe_get s i)) +404: +404: let split_on_char sep s = +404: let r = ref [] in +404: let j = ref (length s) in +404: for i = length s - 1 downto 0 do +404: if unsafe_get s i = sep then begin +404: r := sub s (i + 1) (!j - i - 1) :: !r; +404: j := i +404: end +404: done; +404: sub s 0 !j :: !r +404:end + +402:type bytes = string +402:let output_bytes = output_string + +401:let ( |> ) x f = f x diff --git a/Compat401.ml b/Compat401.ml deleted file mode 100644 index 097fd6e..0000000 --- a/Compat401.ml +++ /dev/null @@ -1,10 +0,0 @@ -(************************************************************************) -(* FlexDLL *) -(* Alain Frisch *) -(* *) -(* Copyright 2007 Institut National de Recherche en Informatique et *) -(* en Automatique. *) -(************************************************************************) - -(* Introduced in 4.01.0 *) -let ( |> ) x f = f x diff --git a/Compat402.ml b/Compat402.ml deleted file mode 100644 index 2221720..0000000 --- a/Compat402.ml +++ /dev/null @@ -1,20 +0,0 @@ -(************************************************************************) -(* FlexDLL *) -(* Alain Frisch *) -(* *) -(* Copyright 2007 Institut National de Recherche en Informatique et *) -(* en Automatique. *) -(************************************************************************) - -(* Back-port required functionality from Bytes in 4.02.0 *) -type bytes = string -module Bytes = struct - include String - - let blit_string = blit - let sub_string = sub - let of_string x = x - let to_string x = x - let cat = (^) -end -let output_bytes = output_string diff --git a/Compat403.ml b/Compat403.ml deleted file mode 100644 index ebbf985..0000000 --- a/Compat403.ml +++ /dev/null @@ -1,45 +0,0 @@ -(************************************************************************) -(* FlexDLL *) -(* Alain Frisch *) -(* *) -(* Copyright 2007 Institut National de Recherche en Informatique et *) -(* en Automatique. *) -(************************************************************************) - -module Char = struct - include Char - - (* Taken from 4.03.0 *) - let lowercase_ascii c = - if (c >= 'A' && c <= 'Z') - then unsafe_chr(code c + 32) - else c - - let uppercase_ascii c = - if (c >= 'a' && c <= 'z') - then unsafe_chr(code c - 32) - else c -end - -module String = struct - include String - - let (lowercase_ascii, uppercase_ascii) = - (* Taken from 4.03.0 (not available before 4.00.0) *) - let map f s = - let l = length s in - if l = 0 then s else begin - (* create and unsafe_set trigger an irrelevant deprecation warning on 4.02.x *) - let r = create l in - for i = 0 to l - 1 do unsafe_set r i (f (unsafe_get s i)) done; - r - end - in - (map Char.lowercase_ascii, map Char.uppercase_ascii) -end - -module Uchar = struct - let unsafe_of_int c = c - - let to_int c = c -end diff --git a/Compat405.ml b/Compat405.ml deleted file mode 100644 index 518f2d3..0000000 --- a/Compat405.ml +++ /dev/null @@ -1,45 +0,0 @@ -(************************************************************************) -(* FlexDLL *) -(* Alain Frisch *) -(* *) -(* Copyright 2007 Institut National de Recherche en Informatique et *) -(* en Automatique. *) -(************************************************************************) - -module Arg = struct - include Arg - - (* Taken from 4.05.0 (not available before 4.05.0) *) - let trim_cr s = - let len = String.length s in - if len > 0 && String.get s (len - 1) = '\r' then - String.sub s 0 (len - 1) - else - s - - let read_aux trim sep file = - let ic = open_in_bin file in - let buf = Buffer.create 200 in - let words = ref [] in - let stash () = - let word = Buffer.contents buf in - let word = if trim then trim_cr word else word in - words := word :: !words; - Buffer.clear buf - in - begin - try while true do - let c = input_char ic in - if c = sep then stash () else Buffer.add_char buf c - done - with End_of_file -> () - end; - if Buffer.length buf > 0 then stash (); - close_in ic; - Array.of_list (List.rev !words) - - let read_arg = read_aux true '\n' - - let read_arg0 = read_aux false '\x00' - -end diff --git a/Compat406.ml b/Compat406.ml deleted file mode 100644 index e9e4e7c..0000000 --- a/Compat406.ml +++ /dev/null @@ -1,30 +0,0 @@ -(************************************************************************) -(* FlexDLL *) -(* Alain Frisch *) -(* *) -(* Copyright 2007 Institut National de Recherche en Informatique et *) -(* en Automatique. *) -(************************************************************************) - -module Buffer = struct - include Buffer - - (* Strictly speaking this should be in Compat402.ml *) - let to_bytes = contents - - (* Taken from 4.06.0 *) - let add_utf_16le_uchar b u = match Uchar.to_int u with - | u when u < 0 -> assert false - | u when u <= 0xFFFF -> - Buffer.add_char b (Char.unsafe_chr (u land 0xFF)); - Buffer.add_char b (Char.unsafe_chr (u lsr 8)) - | u when u <= 0x10FFFF -> - let u' = u - 0x10000 in - let hi = 0xD800 lor (u' lsr 10) in - let lo = 0xDC00 lor (u' land 0x3FF) in - Buffer.add_char b (Char.unsafe_chr (hi land 0xFF)); - Buffer.add_char b (Char.unsafe_chr (hi lsr 8)); - Buffer.add_char b (Char.unsafe_chr (lo land 0xFF)); - Buffer.add_char b (Char.unsafe_chr (lo lsr 8)) - | _ -> assert false -end diff --git a/Compat407.ml b/Compat407.ml deleted file mode 100644 index d0e2526..0000000 --- a/Compat407.ml +++ /dev/null @@ -1,9 +0,0 @@ -(************************************************************************) -(* FlexDLL *) -(* Alain Frisch *) -(* *) -(* Copyright 2007 Institut National de Recherche en Informatique et *) -(* en Automatique. *) -(************************************************************************) - -module Stdlib = Pervasives diff --git a/Makefile b/Makefile index faa3c74..0b1a55f 100644 --- a/Makefile +++ b/Makefile @@ -145,18 +145,19 @@ COMPILER-$(COMPAT_VERSION): rm -f COMPILER-* touch COMPILER-$(COMPAT_VERSION) -test_ver = $(shell if [ $(COMPAT_VERSION) -lt $(1) ] ; then echo lt ; fi) +test_ver = $(shell if [ $(COMPAT_VERSION) -ge $(1) ] ; then echo ge ; fi) # This list must be in order -COMPAT_MODULES := $(if $(call test_ver,40100),Compat401) \ - $(if $(call test_ver,40200),Compat402) \ - $(if $(call test_ver,40300),Compat403) \ - $(if $(call test_ver,40500),Compat405) \ - $(if $(call test_ver,40600),Compat406) \ - $(if $(call test_ver,40700),Compat407) - -Compat.ml: COMPILER-$(COMPAT_VERSION) $(addsuffix .ml, $(COMPAT_MODULES)) - cat $^ > $@ +COMPAT_LEVEL := \ + $(strip $(if $(call test_ver,40100),401) \ + $(if $(call test_ver,40200),402) \ + $(if $(call test_ver,40300),403) \ + $(if $(call test_ver,40500),405) \ + $(if $(call test_ver,40600),406) \ + $(if $(call test_ver,40700),407)) + +Compat.ml: Compat.ml.in COMPILER-$(COMPAT_VERSION) + sed -e '$(if $(COMPAT_LEVEL),/^$(subst $(SPACE),:\|^,$(COMPAT_LEVEL)):/d;)s/^[0-9]*://' $< > $@ flexlink.exe: $(OBJS) $(RES) @echo Building flexlink.exe with TOOLCHAIN=$(TOOLCHAIN) for OCaml $(OCAML_VERSION) diff --git a/cmdline.ml b/cmdline.ml index 17f2c3c..37a3a41 100644 --- a/cmdline.ml +++ b/cmdline.ml @@ -252,7 +252,10 @@ let parse_cmdline () = "-link" :: String.sub s 5 (String.length s - 5) :: tr rest (* Convert gcc linker option prefix -Wl, to flexlink linker prefix -link *) | s :: rest when String.length s >= 6 && String.sub s 0 5 = "-Wl,-" -> - "-link" :: String.sub s 4 (String.length s - 4) :: tr rest + let args = + String.split_on_char ',' (String.sub s 4 (String.length s - 4)) + in + List.fold_right (fun arg args -> "-link" :: arg :: args) args (tr rest) | "-arg" :: x :: rest -> tr (Array.to_list (Arg.read_arg x)) @ rest | "-arg0" :: x :: rest ->