Move patches to external git repo.
http://git.fedorahosted.org/git/?p=fedora-ocaml.git
This commit is contained in:
		
							parent
							
								
									7b1e4c1b84
								
							
						
					
					
						commit
						a07112286b
					
				
							
								
								
									
										240
									
								
								0001-ocamlbyteinfo-ocamlplugininfo-Useful-utilities-from-.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										240
									
								
								0001-ocamlbyteinfo-ocamlplugininfo-Useful-utilities-from-.patch
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,240 @@ | ||||
| From 0f3d9e1188a765390ac21b6204c66765c1cad8f0 Mon Sep 17 00:00:00 2001 | ||||
| From: "Richard W.M. Jones" <rjones@redhat.com> | ||||
| Date: Tue, 29 May 2012 20:40:36 +0100 | ||||
| Subject: [PATCH 1/7] ocamlbyteinfo, ocamlplugininfo: Useful utilities from | ||||
|  Debian, sent upstream. | ||||
| 
 | ||||
| See: | ||||
| http://git.debian.org/?p=pkg-ocaml-maint/packages/ocaml.git;a=tree;f=debian/ocamlbyteinfo;hb=HEAD | ||||
| ---
 | ||||
|  ocamlbyteinfo.ml   |  101 ++++++++++++++++++++++++++++++++++++++++++++++++ | ||||
|  ocamlplugininfo.ml |  109 ++++++++++++++++++++++++++++++++++++++++++++++++++++ | ||||
|  2 files changed, 210 insertions(+) | ||||
|  create mode 100644 ocamlbyteinfo.ml | ||||
|  create mode 100644 ocamlplugininfo.ml | ||||
| 
 | ||||
| diff --git a/ocamlbyteinfo.ml b/ocamlbyteinfo.ml
 | ||||
| new file mode 100644 | ||||
| index 0000000..eb9a293
 | ||||
| --- /dev/null
 | ||||
| +++ b/ocamlbyteinfo.ml
 | ||||
| @@ -0,0 +1,101 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| +(*                           Objective Caml                            *)
 | ||||
| +(*                                                                     *)
 | ||||
| +(*            Xavier Leroy, projet Gallium, INRIA Rocquencourt         *)
 | ||||
| +(*                                                                     *)
 | ||||
| +(*  Copyright 2009 Institut National de Recherche en Informatique et   *)
 | ||||
| +(*  en Automatique.  All rights reserved.  This file is distributed    *)
 | ||||
| +(*  under the terms of the GNU Library General Public License, with    *)
 | ||||
| +(*  the special exception on linking described in file ../../LICENSE.  *)
 | ||||
| +(*                                                                     *)
 | ||||
| +(***********************************************************************)
 | ||||
| +
 | ||||
| +(* $Id$ *)
 | ||||
| +
 | ||||
| +(* Dumps a bytecode binary file *)
 | ||||
| +
 | ||||
| +open Sys
 | ||||
| +open Dynlinkaux
 | ||||
| +
 | ||||
| +let input_stringlist ic len =
 | ||||
| +  let get_string_list sect len =
 | ||||
| +    let rec fold s e acc =
 | ||||
| +      if e != len then
 | ||||
| +        if sect.[e] = '\000' then
 | ||||
| +          fold (e+1) (e+1) (String.sub sect s (e-s) :: acc)
 | ||||
| +        else fold s (e+1) acc
 | ||||
| +      else acc
 | ||||
| +    in fold 0 0 []
 | ||||
| +  in
 | ||||
| +  let sect = String.create len in
 | ||||
| +  let _ = really_input ic sect 0 len in
 | ||||
| +  get_string_list sect len
 | ||||
| +
 | ||||
| +let print = Printf.printf
 | ||||
| +let perr s =
 | ||||
| +  Printf.eprintf "%s\n" s;
 | ||||
| +  exit(1)
 | ||||
| +let p_title title = print "%s:\n" title
 | ||||
| +
 | ||||
| +let p_section title format pdata = function
 | ||||
| +  | [] -> ()
 | ||||
| +  | l ->
 | ||||
| +      p_title title;
 | ||||
| +      List.iter
 | ||||
| +        (fun (name, data) -> print format (pdata data) name)
 | ||||
| +        l
 | ||||
| +
 | ||||
| +let p_list title format = function
 | ||||
| +  | [] -> ()
 | ||||
| +  | l ->
 | ||||
| +      p_title title;
 | ||||
| +      List.iter
 | ||||
| +        (fun name -> print format name)
 | ||||
| +        l
 | ||||
| +
 | ||||
| +let _ =
 | ||||
| +  try
 | ||||
| +    let input_name = Sys.argv.(1) in
 | ||||
| +    let ic = open_in_bin input_name in
 | ||||
| +    Bytesections.read_toc ic;
 | ||||
| +    List.iter
 | ||||
| +      (fun section ->
 | ||||
| +         try
 | ||||
| +           let len = Bytesections.seek_section ic section in
 | ||||
| +           if len > 0 then match section with
 | ||||
| +             | "CRCS" ->
 | ||||
| +                 p_section
 | ||||
| +                   "Imported Units"
 | ||||
| +                   "\t%s\t%s\n"
 | ||||
| +                   Digest.to_hex
 | ||||
| +                   (input_value ic : (string * Digest.t) list)
 | ||||
| +             | "DLLS" ->
 | ||||
| +                 p_list
 | ||||
| +                   "Used Dlls" "\t%s\n"
 | ||||
| +                   (input_stringlist ic len)
 | ||||
| +             | "DLPT" ->
 | ||||
| +                 p_list
 | ||||
| +                   "Additional Dll paths"
 | ||||
| +                   "\t%s\n"
 | ||||
| +                   (input_stringlist ic len)
 | ||||
| +             | "PRIM" ->
 | ||||
| +                 let prims = (input_stringlist ic len) in
 | ||||
| +                 print "Uses unsafe features: ";
 | ||||
| +                 begin match prims with
 | ||||
| +                     [] -> print "no\n"
 | ||||
| +                   | l  -> print "YES\n";
 | ||||
| +                       p_list "Primitives declared in this module"
 | ||||
| +                         "\t%s\n"
 | ||||
| +                         l
 | ||||
| +                 end
 | ||||
| +             | _ -> ()
 | ||||
| +         with Not_found | Failure _ | Invalid_argument _ -> ()
 | ||||
| +      )
 | ||||
| +      ["CRCS"; "DLLS"; "DLPT"; "PRIM"];
 | ||||
| +    close_in ic
 | ||||
| +  with
 | ||||
| +    | Sys_error msg ->
 | ||||
| +        perr msg
 | ||||
| +    | Invalid_argument("index out of bounds") ->
 | ||||
| +        perr (Printf.sprintf "Usage: %s filename" Sys.argv.(0))
 | ||||
| diff --git a/ocamlplugininfo.ml b/ocamlplugininfo.ml
 | ||||
| new file mode 100644 | ||||
| index 0000000..e28800f
 | ||||
| --- /dev/null
 | ||||
| +++ b/ocamlplugininfo.ml
 | ||||
| @@ -0,0 +1,109 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| +(*                           Objective Caml                            *)
 | ||||
| +(*                                                                     *)
 | ||||
| +(*            Xavier Leroy, projet Gallium, INRIA Rocquencourt         *)
 | ||||
| +(*                                                                     *)
 | ||||
| +(*  Copyright 2009 Institut National de Recherche en Informatique et   *)
 | ||||
| +(*  en Automatique.  All rights reserved.  This file is distributed    *)
 | ||||
| +(*  under the terms of the GNU Library General Public License, with    *)
 | ||||
| +(*  the special exception on linking described in file ../../LICENSE.  *)
 | ||||
| +(*                                                                     *)
 | ||||
| +(***********************************************************************)
 | ||||
| +
 | ||||
| +(* $Id$ *)
 | ||||
| +
 | ||||
| +(* Dumps a .cmxs file *)
 | ||||
| +
 | ||||
| +open Natdynlink
 | ||||
| +open Format
 | ||||
| +
 | ||||
| +let file =
 | ||||
| +  try
 | ||||
| +    Sys.argv.(1)
 | ||||
| +  with _ -> begin
 | ||||
| +    Printf.eprintf "Usage: %s file.cmxs\n" Sys.argv.(0);
 | ||||
| +    exit(1)
 | ||||
| +  end
 | ||||
| +
 | ||||
| +exception Abnormal_exit
 | ||||
| +
 | ||||
| +let error s e =
 | ||||
| +  let eprint = Printf.eprintf in
 | ||||
| +  let print_exc s = function
 | ||||
| +    | End_of_file ->
 | ||||
| +       eprint "%s: %s\n" s file
 | ||||
| +    | Abnormal_exit ->
 | ||||
| +        eprint "%s\n" s
 | ||||
| +    | e -> eprint "%s\n" (Printexc.to_string e)
 | ||||
| +  in
 | ||||
| +    print_exc s e;
 | ||||
| +    exit(1)
 | ||||
| +
 | ||||
| +let read_in command =
 | ||||
| +  let cmd = Printf.sprintf command file in
 | ||||
| +  let ic = Unix.open_process_in cmd in
 | ||||
| +  try
 | ||||
| +    let line = input_line ic in
 | ||||
| +    begin match (Unix.close_process_in ic) with
 | ||||
| +      | Unix.WEXITED 0 -> Str.split (Str.regexp "[ ]+") line
 | ||||
| +      | Unix.WEXITED _  | Unix.WSIGNALED _ | Unix.WSTOPPED _ ->
 | ||||
| +          error
 | ||||
| +            (Printf.sprintf
 | ||||
| +               "Command \"%s\" exited abnormally"
 | ||||
| +               cmd
 | ||||
| +            )
 | ||||
| +            Abnormal_exit
 | ||||
| +    end
 | ||||
| +  with e -> error "File is empty" e
 | ||||
| +
 | ||||
| +let get_offset adr_off adr_sec =
 | ||||
| +  try
 | ||||
| +    let adr = List.nth adr_off 4 in
 | ||||
| +    let off = List.nth adr_off 5 in
 | ||||
| +    let sec = List.hd adr_sec in
 | ||||
| +
 | ||||
| +    let (!) x = Int64.of_string ("0x" ^ x) in
 | ||||
| +    let (+) = Int64.add in
 | ||||
| +    let (-) = Int64.sub in
 | ||||
| +
 | ||||
| +      Int64.to_int (!off + !sec - !adr)
 | ||||
| +
 | ||||
| +  with Failure _ | Invalid_argument _ ->
 | ||||
| +    error
 | ||||
| +      "Command output doesn't have the expected format"
 | ||||
| +      Abnormal_exit
 | ||||
| +
 | ||||
| +let print_infos name crc defines cmi cmx =
 | ||||
| +  let print_name_crc (name, crc) =
 | ||||
| +    printf "@ %s (%s)" name (Digest.to_hex crc)
 | ||||
| +  in
 | ||||
| +  let pr_imports ppf imps = List.iter print_name_crc imps in
 | ||||
| +  printf "Name: %s@." name;
 | ||||
| +  printf "CRC of implementation: %s@." (Digest.to_hex crc);
 | ||||
| +  printf "@[<hov 2>Globals defined:";
 | ||||
| +  List.iter (fun s -> printf "@ %s" s) defines;
 | ||||
| +  printf "@]@.";
 | ||||
| +  printf "@[<v 2>Interfaces imported:%a@]@." pr_imports cmi;
 | ||||
| +  printf "@[<v 2>Implementations imported:%a@]@." pr_imports cmx
 | ||||
| +
 | ||||
| +let _ =
 | ||||
| +  let adr_off = read_in "objdump -h %s | grep ' .data '" in
 | ||||
| +  let adr_sec = read_in "objdump -T %s | grep ' caml_plugin_header$'" in
 | ||||
| +
 | ||||
| +  let ic = open_in file in
 | ||||
| +  let _ = seek_in ic (get_offset adr_off adr_sec) in
 | ||||
| +  let header  = (input_value ic : Natdynlink.dynheader) in
 | ||||
| +    if header.magic <> Natdynlink.dyn_magic_number then
 | ||||
| +      raise(Error(Natdynlink.Not_a_bytecode_file file))
 | ||||
| +    else begin
 | ||||
| +      List.iter
 | ||||
| +        (fun ui ->
 | ||||
| +           print_infos
 | ||||
| +             ui.name
 | ||||
| +             ui.crc
 | ||||
| +             ui.defines
 | ||||
| +             ui.imports_cmi
 | ||||
| +             ui.imports_cmx)
 | ||||
| +        header.units
 | ||||
| +    end
 | ||||
| -- 
 | ||||
| 1.7.10 | ||||
| 
 | ||||
							
								
								
									
										2583
									
								
								0002-GNU-config.guess-and-config.sub-replacements.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										2583
									
								
								0002-GNU-config.guess-and-config.sub-replacements.patch
									
									
									
									
									
										Normal file
									
								
							
										
											
												File diff suppressed because it is too large
												Load Diff
											
										
									
								
							
							
								
								
									
										26
									
								
								0003-Don-t-add-rpaths-to-libraries.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										26
									
								
								0003-Don-t-add-rpaths-to-libraries.patch
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,26 @@ | ||||
| From 649d2c547fd28c48b52348328cd267854389f45f Mon Sep 17 00:00:00 2001 | ||||
| From: "Richard W.M. Jones" <rjones@redhat.com> | ||||
| Date: Tue, 29 May 2012 20:43:34 +0100 | ||||
| Subject: [PATCH 3/7] Don't add rpaths to libraries. | ||||
| 
 | ||||
| ---
 | ||||
|  tools/Makefile.shared |    3 --- | ||||
|  1 file changed, 3 deletions(-) | ||||
| 
 | ||||
| diff --git a/tools/Makefile.shared b/tools/Makefile.shared
 | ||||
| index 247575a..05de46c 100644
 | ||||
| --- a/tools/Makefile.shared
 | ||||
| +++ b/tools/Makefile.shared
 | ||||
| @@ -103,9 +103,6 @@ ocamlmklib.ml: ocamlmklib.mlp ../config/Makefile
 | ||||
|  	sed -e "s|%%BINDIR%%|$(BINDIR)|" \ | ||||
|  	    -e "s|%%SUPPORTS_SHARED_LIBRARIES%%|$(SUPPORTS_SHARED_LIBRARIES)|" \ | ||||
|  	    -e "s|%%MKSHAREDLIB%%|$(MKSHAREDLIB)|" \ | ||||
| -	    -e "s|%%BYTECCRPATH%%|$(BYTECCRPATH)|" \
 | ||||
| -	    -e "s|%%NATIVECCRPATH%%|$(NATIVECCRPATH)|" \
 | ||||
| -	    -e "s|%%MKSHAREDLIBRPATH%%|$(MKSHAREDLIBRPATH)|" \
 | ||||
|  	    -e "s|%%RANLIB%%|$(RANLIB)|" \ | ||||
|  	  ocamlmklib.mlp >> ocamlmklib.ml | ||||
|   | ||||
| -- 
 | ||||
| 1.7.10 | ||||
| 
 | ||||
							
								
								
									
										27
									
								
								0004-configure-Allow-user-defined-C-compiler-flags.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										27
									
								
								0004-configure-Allow-user-defined-C-compiler-flags.patch
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,27 @@ | ||||
| From 0febdfe1698639ce53e6ed8935cdc573be302b49 Mon Sep 17 00:00:00 2001 | ||||
| From: "Richard W.M. Jones" <rjones@redhat.com> | ||||
| Date: Tue, 29 May 2012 20:44:18 +0100 | ||||
| Subject: [PATCH 4/7] configure: Allow user defined C compiler flags. | ||||
| 
 | ||||
| ---
 | ||||
|  configure |    4 ++++ | ||||
|  1 file changed, 4 insertions(+) | ||||
| 
 | ||||
| diff --git a/configure b/configure
 | ||||
| index 9be5199..d0a6b0f 100755
 | ||||
| --- a/configure
 | ||||
| +++ b/configure
 | ||||
| @@ -1600,6 +1600,10 @@ case "$buggycc" in
 | ||||
|      nativecccompopts="$nativecccompopts -fomit-frame-pointer";; | ||||
|  esac | ||||
|   | ||||
| +# Allow user defined C Compiler flags
 | ||||
| +bytecccompopts="$bytecccompopts $CFLAGS"
 | ||||
| +nativecccompopts="$nativecccompopts $CFLAGS"
 | ||||
| +
 | ||||
|  # Finish generated files | ||||
|   | ||||
|  cclibs="$cclibs $mathlib" | ||||
| -- 
 | ||||
| 1.7.10 | ||||
| 
 | ||||
| @ -1,6 +1,7 @@ | ||||
| From e3b5b13c53b62b99c4d6764b52a7269a6fe5b983 Mon Sep 17 00:00:00 2001 | ||||
| From: Stephane Glondu <steph@glondu.net> | ||||
| Date: Fri, 12 Aug 2011 21:13:17 +0200 | ||||
| Subject: ocamlopt/arm: add .type directive for code symbols | ||||
| Date: Tue, 29 May 2012 20:45:32 +0100 | ||||
| Subject: [PATCH 5/7] ocamlopt/arm: add .type directive for code symbols | ||||
| 
 | ||||
| Bug: http://caml.inria.fr/mantis/view.php?id=5336 | ||||
| Bug-Ubuntu: https://bugs.launchpad.net/bugs/810402 | ||||
| @ -8,7 +9,7 @@ Signed-off-by: Stephane Glondu <steph@glondu.net> | ||||
| ---
 | ||||
|  asmcomp/arm/emit.mlp |    1 + | ||||
|  asmrun/arm.S         |   12 ++++++++++++ | ||||
|  2 files changed, 13 insertions(+), 0 deletions(-) | ||||
|  2 files changed, 13 insertions(+) | ||||
| 
 | ||||
| diff --git a/asmcomp/arm/emit.mlp b/asmcomp/arm/emit.mlp
 | ||||
| index 2003313..a4b2241 100644
 | ||||
| @ -123,3 +124,5 @@ index 164f731..1313e9c 100644 | ||||
|      /* Load address of [caml_array_bound_error] in r12 */ | ||||
|          ldr     r12, .Lcaml_array_bound_error | ||||
| -- 
 | ||||
| 1.7.10 | ||||
| 
 | ||||
| @ -1,6 +1,41 @@ | ||||
| diff -uNr ocaml-3.10.1/asmcomp/power64/arch.ml ocaml-3.10.1.ppc64/asmcomp/power64/arch.ml
 | ||||
| --- ocaml-3.10.1/asmcomp/power64/arch.ml        1969-12-31 19:00:00.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmcomp/power64/arch.ml  2008-02-29 08:37:45.000000000 -0500
 | ||||
| From a9648ff01cea44e6892663e97c3c388686b4fcd7 Mon Sep 17 00:00:00 2001 | ||||
| From: "Richard W.M. Jones" <rjones@redhat.com> | ||||
| Date: Tue, 29 May 2012 20:47:07 +0100 | ||||
| Subject: [PATCH 6/7] Add support for ppc64. | ||||
| 
 | ||||
| Note (1): This patch was rejected upstream because they don't have | ||||
| appropriate hardware for testing. | ||||
| 
 | ||||
| Note (2): Upstream powerpc directory has some support for ppc64, but | ||||
| only for Macs, and I couldn't get it to work at all with IBM hardware. | ||||
| 
 | ||||
| This patch was collaborated on by several people, most notably David | ||||
| Woodhouse. | ||||
| ---
 | ||||
|  asmcomp/power64/arch.ml       |   84 ++++ | ||||
|  asmcomp/power64/emit.mlp      |  989 +++++++++++++++++++++++++++++++++++++++++ | ||||
|  asmcomp/power64/proc.ml       |  245 ++++++++++ | ||||
|  asmcomp/power64/reload.ml     |   18 + | ||||
|  asmcomp/power64/scheduling.ml |   66 +++ | ||||
|  asmcomp/power64/selection.ml  |  103 +++++ | ||||
|  asmrun/Makefile               |    6 + | ||||
|  asmrun/power64-elf.S          |  486 ++++++++++++++++++++ | ||||
|  asmrun/stack.h                |    9 + | ||||
|  configure                     |    5 +- | ||||
|  10 files changed, 2010 insertions(+), 1 deletion(-) | ||||
|  create mode 100644 asmcomp/power64/arch.ml | ||||
|  create mode 100644 asmcomp/power64/emit.mlp | ||||
|  create mode 100644 asmcomp/power64/proc.ml | ||||
|  create mode 100644 asmcomp/power64/reload.ml | ||||
|  create mode 100644 asmcomp/power64/scheduling.ml | ||||
|  create mode 100644 asmcomp/power64/selection.ml | ||||
|  create mode 100644 asmrun/power64-elf.S | ||||
| 
 | ||||
| diff --git a/asmcomp/power64/arch.ml b/asmcomp/power64/arch.ml
 | ||||
| new file mode 100644 | ||||
| index 0000000..93b5b18
 | ||||
| --- /dev/null
 | ||||
| +++ b/asmcomp/power64/arch.ml
 | ||||
| @@ -0,0 +1,84 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| @ -86,9 +121,11 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/arch.ml ocaml-3.10.1.ppc64/asmcomp/power6 | ||||
| +  | Ialloc_far n ->
 | ||||
| +      fprintf ppf "alloc_far %d" n
 | ||||
| +
 | ||||
| diff -uNr ocaml-3.10.1/asmcomp/power64/emit.mlp ocaml-3.10.1.ppc64/asmcomp/power64/emit.mlp
 | ||||
| --- ocaml-3.10.1/asmcomp/power64/emit.mlp       1969-12-31 19:00:00.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmcomp/power64/emit.mlp 2008-02-29 08:37:45.000000000 -0500
 | ||||
| diff --git a/asmcomp/power64/emit.mlp b/asmcomp/power64/emit.mlp
 | ||||
| new file mode 100644 | ||||
| index 0000000..95eb193
 | ||||
| --- /dev/null
 | ||||
| +++ b/asmcomp/power64/emit.mlp
 | ||||
| @@ -0,0 +1,989 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| @ -1079,9 +1116,11 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/emit.mlp ocaml-3.10.1.ppc64/asmcomp/power | ||||
| +  `    .quad   {emit_int (List.length !frame_descriptors)}\n`;
 | ||||
| +  List.iter emit_frame !frame_descriptors;
 | ||||
| +  frame_descriptors := []
 | ||||
| diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power64/proc.ml
 | ||||
| --- ocaml-3.10.1/asmcomp/power64/proc.ml        1969-12-31 19:00:00.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmcomp/power64/proc.ml  2008-02-29 08:37:45.000000000 -0500
 | ||||
| diff --git a/asmcomp/power64/proc.ml b/asmcomp/power64/proc.ml
 | ||||
| new file mode 100644 | ||||
| index 0000000..95bf6c4
 | ||||
| --- /dev/null
 | ||||
| +++ b/asmcomp/power64/proc.ml
 | ||||
| @@ -0,0 +1,245 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| @ -1328,9 +1367,11 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power6 | ||||
| +
 | ||||
| +open Clflags;;
 | ||||
| +open Config;;
 | ||||
| diff -uNr ocaml-3.10.1/asmcomp/power64/reload.ml ocaml-3.10.1.ppc64/asmcomp/power64/reload.ml
 | ||||
| --- ocaml-3.10.1/asmcomp/power64/reload.ml      1969-12-31 19:00:00.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmcomp/power64/reload.ml        2008-02-29 08:37:45.000000000 -0500
 | ||||
| diff --git a/asmcomp/power64/reload.ml b/asmcomp/power64/reload.ml
 | ||||
| new file mode 100644 | ||||
| index 0000000..42d5d4d
 | ||||
| --- /dev/null
 | ||||
| +++ b/asmcomp/power64/reload.ml
 | ||||
| @@ -0,0 +1,18 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| @ -1350,9 +1391,11 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/reload.ml ocaml-3.10.1.ppc64/asmcomp/powe | ||||
| +
 | ||||
| +let fundecl f =
 | ||||
| +  (new Reloadgen.reload_generic)#fundecl f
 | ||||
| diff -uNr ocaml-3.10.1/asmcomp/power64/scheduling.ml ocaml-3.10.1.ppc64/asmcomp/power64/scheduling.ml
 | ||||
| --- ocaml-3.10.1/asmcomp/power64/scheduling.ml  1969-12-31 19:00:00.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmcomp/power64/scheduling.ml    2008-02-29 08:37:45.000000000 -0500
 | ||||
| diff --git a/asmcomp/power64/scheduling.ml b/asmcomp/power64/scheduling.ml
 | ||||
| new file mode 100644 | ||||
| index 0000000..d73e333
 | ||||
| --- /dev/null
 | ||||
| +++ b/asmcomp/power64/scheduling.ml
 | ||||
| @@ -0,0 +1,66 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| @ -1420,9 +1463,11 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/scheduling.ml ocaml-3.10.1.ppc64/asmcomp/ | ||||
| +
 | ||||
| +let fundecl f = (new scheduler)#schedule_fundecl f
 | ||||
| +
 | ||||
| diff -uNr ocaml-3.10.1/asmcomp/power64/selection.ml ocaml-3.10.1.ppc64/asmcomp/power64/selection.ml
 | ||||
| --- ocaml-3.10.1/asmcomp/power64/selection.ml   1969-12-31 19:00:00.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmcomp/power64/selection.ml     2008-02-29 08:37:45.000000000 -0500
 | ||||
| diff --git a/asmcomp/power64/selection.ml b/asmcomp/power64/selection.ml
 | ||||
| new file mode 100644 | ||||
| index 0000000..afc7649
 | ||||
| --- /dev/null
 | ||||
| +++ b/asmcomp/power64/selection.ml
 | ||||
| @@ -0,0 +1,103 @@
 | ||||
| +(***********************************************************************)
 | ||||
| +(*                                                                     *)
 | ||||
| @ -1527,12 +1572,13 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/selection.ml ocaml-3.10.1.ppc64/asmcomp/p | ||||
| +end
 | ||||
| +
 | ||||
| +let fundecl f = (new selector)#emit_fundecl f
 | ||||
| diff -uNr ocaml-3.10.1/asmrun/Makefile ocaml-3.10.1.ppc64/asmrun/Makefile
 | ||||
| --- ocaml-3.10.1/asmrun/Makefile        2007-02-23 04:29:45.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmrun/Makefile  2008-02-29 08:37:45.000000000 -0500
 | ||||
| @@ -74,6 +74,12 @@
 | ||||
| diff --git a/asmrun/Makefile b/asmrun/Makefile
 | ||||
| index efffa33..3525b82 100644
 | ||||
| --- a/asmrun/Makefile
 | ||||
| +++ b/asmrun/Makefile
 | ||||
| @@ -74,6 +74,12 @@ power.o: power-$(SYSTEM).o
 | ||||
|  power.p.o: power-$(SYSTEM).o | ||||
| 	cp power-$(SYSTEM).o power.p.o | ||||
|  	cp power-$(SYSTEM).o power.p.o | ||||
|   | ||||
| +power64.o: power64-$(SYSTEM).o
 | ||||
| +	cp power64-$(SYSTEM).o power64.o
 | ||||
| @ -1541,11 +1587,13 @@ diff -uNr ocaml-3.10.1/asmrun/Makefile ocaml-3.10.1.ppc64/asmrun/Makefile | ||||
| +	cp power64-$(SYSTEM).o power64.p.o
 | ||||
| +
 | ||||
|  main.c: ../byterun/main.c | ||||
|         ln -s ../byterun/main.c main.c | ||||
|  	ln -s ../byterun/main.c main.c | ||||
|  misc.c: ../byterun/misc.c | ||||
| diff -uNr ocaml-3.10.1/asmrun/power64-elf.S ocaml-3.10.1.ppc64/asmrun/power64-elf.S
 | ||||
| --- ocaml-3.10.1/asmrun/power64-elf.S   1969-12-31 19:00:00.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmrun/power64-elf.S     2008-02-29 08:37:45.000000000 -0500
 | ||||
| diff --git a/asmrun/power64-elf.S b/asmrun/power64-elf.S
 | ||||
| new file mode 100644 | ||||
| index 0000000..b2c24d6
 | ||||
| --- /dev/null
 | ||||
| +++ b/asmrun/power64-elf.S
 | ||||
| @@ -0,0 +1,486 @@
 | ||||
| +/*********************************************************************/
 | ||||
| +/*                                                                   */
 | ||||
| @ -2033,9 +2081,10 @@ diff -uNr ocaml-3.10.1/asmrun/power64-elf.S ocaml-3.10.1.ppc64/asmrun/power64-el | ||||
| +        .short  0               /* no roots here */
 | ||||
| +        .align  3
 | ||||
| +
 | ||||
| diff -uNr ocaml-3.10.1/asmrun/stack.h ocaml-3.10.1.ppc64/asmrun/stack.h
 | ||||
| --- ocaml-3.10.1/asmrun/stack.h 2007-02-15 13:35:20.000000000 -0500
 | ||||
| +++ ocaml-3.10.1.ppc64/asmrun/stack.h   2008-02-29 08:37:45.000000000 -0500
 | ||||
| diff --git a/asmrun/stack.h b/asmrun/stack.h
 | ||||
| index c778873..f1d2e6a 100644
 | ||||
| --- a/asmrun/stack.h
 | ||||
| +++ b/asmrun/stack.h
 | ||||
| @@ -65,6 +65,15 @@
 | ||||
|  #define Callback_link(sp) ((struct caml_context *)((sp) + Trap_frame_size)) | ||||
|  #endif | ||||
| @ -2052,10 +2101,11 @@ diff -uNr ocaml-3.10.1/asmrun/stack.h ocaml-3.10.1.ppc64/asmrun/stack.h | ||||
|  #ifdef TARGET_m68k | ||||
|  #define Saved_return_address(sp) *((intnat *)((sp) - 4)) | ||||
|  #define Callback_link(sp) ((struct caml_context *)((sp) + 8)) | ||||
| diff -uNr ocaml-3.11.0+beta1/configure ocaml-3.11.0+beta1.ppc64/configure
 | ||||
| --- ocaml-3.11.0+beta1/configure.ppc64  2008-11-18 15:46:57.000000000 +0000
 | ||||
| +++ ocaml-3.11.0+beta1/configure        2008-11-18 15:49:19.000000000 +0000
 | ||||
| @@ -632,6 +632,7 @@
 | ||||
| diff --git a/configure b/configure
 | ||||
| index d0a6b0f..6ed0a9c 100755
 | ||||
| --- a/configure
 | ||||
| +++ b/configure
 | ||||
| @@ -685,6 +685,7 @@ case "$host" in
 | ||||
|    hppa2.0*-*-hpux*)             arch=hppa; system=hpux;; | ||||
|    hppa*-*-linux*)               arch=hppa; system=linux;; | ||||
|    hppa*-*-gnu*)                 arch=hppa; system=gnu;; | ||||
| @ -2063,7 +2113,7 @@ diff -uNr ocaml-3.11.0+beta1/configure ocaml-3.11.0+beta1.ppc64/configure | ||||
|    powerpc*-*-linux*)            arch=power; model=ppc; system=elf;; | ||||
|    powerpc-*-netbsd*)            arch=power; model=ppc; system=elf;; | ||||
|    powerpc-*-rhapsody*)          arch=power; model=ppc; system=rhapsody;; | ||||
| @@ -655,7 +656,7 @@
 | ||||
| @@ -709,7 +710,7 @@ esac
 | ||||
|   | ||||
|  if $arch64; then | ||||
|    case "$arch,$model" in | ||||
| @ -2072,7 +2122,7 @@ diff -uNr ocaml-3.11.0+beta1/configure ocaml-3.11.0+beta1.ppc64/configure | ||||
|        arch=none; model=default; system=unknown;; | ||||
|    esac | ||||
|  fi | ||||
| @@ -712,6 +713,8 @@
 | ||||
| @@ -772,6 +773,8 @@ case "$arch,$model,$system" in
 | ||||
|                      aspp='as -n32 -O2';; | ||||
|    power,*,elf)      as='as -u -m ppc' | ||||
|                      aspp='gcc -c';; | ||||
| @ -2081,3 +2131,6 @@ diff -uNr ocaml-3.11.0+beta1/configure ocaml-3.11.0+beta1.ppc64/configure | ||||
|    power,*,bsd)      as='as' | ||||
|                      aspp='gcc -c';; | ||||
|    power,*,rhapsody) as="as -arch $model" | ||||
| -- 
 | ||||
| 1.7.10 | ||||
| 
 | ||||
| @ -1,7 +1,33 @@ | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/amd64/selection.ml ocaml-3.12.1-arm/asmcomp/amd64/selection.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/amd64/selection.ml	2010-04-08 04:58:41.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/amd64/selection.ml	2012-04-28 12:19:05.173844703 +0100
 | ||||
| @@ -121,7 +121,7 @@
 | ||||
| From 03318d9e7ef402f137dd100fe31bd01c37c1b94f Mon Sep 17 00:00:00 2001 | ||||
| From: "Richard W.M. Jones" <rjones@redhat.com> | ||||
| Date: Tue, 29 May 2012 20:50:42 +0100 | ||||
| Subject: [PATCH 7/7] New ARM backend, written by Benedikt Meurer (PR#5433). | ||||
| 
 | ||||
| Backported from upstream sources to 3.12.1 by RWMJ. | ||||
| ---
 | ||||
|  asmcomp/amd64/selection.ml   |   14 +- | ||||
|  asmcomp/arm/arch.ml          |  152 +++++++- | ||||
|  asmcomp/arm/emit.mlp         |  850 ++++++++++++++++++++++++++++-------------- | ||||
|  asmcomp/arm/proc.ml          |  185 ++++++--- | ||||
|  asmcomp/arm/reload.ml        |    4 +- | ||||
|  asmcomp/arm/scheduling.ml    |   80 ++-- | ||||
|  asmcomp/arm/selection.ml     |  343 ++++++++++------- | ||||
|  asmcomp/i386/selection.ml    |   14 +- | ||||
|  asmcomp/power/selection.ml   |    2 +- | ||||
|  asmcomp/power64/selection.ml |    2 +- | ||||
|  asmcomp/selectgen.ml         |   13 +- | ||||
|  asmcomp/selectgen.mli        |    2 +- | ||||
|  asmcomp/sparc/selection.ml   |    2 +- | ||||
|  asmrun/arm.S                 |  544 ++++++++++++++++----------- | ||||
|  asmrun/signals_osdep.h       |    2 +- | ||||
|  configure                    |   11 +- | ||||
|  16 files changed, 1477 insertions(+), 743 deletions(-) | ||||
| 
 | ||||
| diff --git a/asmcomp/amd64/selection.ml b/asmcomp/amd64/selection.ml
 | ||||
| index f0546cf..5d9f6fa 100644
 | ||||
| --- a/asmcomp/amd64/selection.ml
 | ||||
| +++ b/asmcomp/amd64/selection.ml
 | ||||
| @@ -121,7 +121,7 @@ method is_immediate n = n <= 0x7FFFFFFF && n >= -0x80000000
 | ||||
|   | ||||
|  method is_immediate_natint n = n <= 0x7FFFFFFFn && n >= -0x80000000n | ||||
|   | ||||
| @ -10,7 +36,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/amd64/selection.ml ocaml-3.12.1-arm/asmcomp | ||||
|    let (a, d) = select_addr exp in | ||||
|    (* PR#4625: displacement must be a signed 32-bit immediate *) | ||||
|    if d < -0x8000_0000 || d > 0x7FFF_FFFF | ||||
| @@ -157,7 +157,7 @@
 | ||||
| @@ -157,7 +157,7 @@ method! select_operation op args =
 | ||||
|    match op with | ||||
|    (* Recognize the LEA instruction *) | ||||
|      Caddi | Cadda | Csubi | Csuba -> | ||||
| @ -19,7 +45,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/amd64/selection.ml ocaml-3.12.1-arm/asmcomp | ||||
|          (Iindexed d, _) -> super#select_operation op args | ||||
|        | (Iindexed2 0, _) -> super#select_operation op args | ||||
|        | (addr, arg) -> (Ispecific(Ilea addr), [arg]) | ||||
| @@ -191,7 +191,7 @@
 | ||||
| @@ -191,7 +191,7 @@ method! select_operation op args =
 | ||||
|        begin match args with | ||||
|          [loc; Cop(Caddi, [Cop(Cload _, [loc']); Cconst_int n])] | ||||
|          when loc = loc' && self#is_immediate n -> | ||||
| @ -28,7 +54,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/amd64/selection.ml ocaml-3.12.1-arm/asmcomp | ||||
|            (Ispecific(Ioffset_loc(n, addr)), [arg]) | ||||
|        | _ -> | ||||
|            super#select_operation op args | ||||
| @@ -202,12 +202,12 @@
 | ||||
| @@ -202,12 +202,12 @@ method! select_operation op args =
 | ||||
|   | ||||
|  method select_floatarith commutative regular_op mem_op args = | ||||
|    match args with | ||||
| @ -45,9 +71,10 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/amd64/selection.ml ocaml-3.12.1-arm/asmcomp | ||||
|        (Ispecific(Ifloatarithmem(mem_op, addr)), | ||||
|                   [arg2; arg1]) | ||||
|    | [arg1; arg2] -> | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/arm/arch.ml ocaml-3.12.1-arm/asmcomp/arm/arch.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/arm/arch.ml	2002-11-29 15:03:37.000000000 +0000
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/arm/arch.ml	2012-04-28 09:20:35.016065972 +0100
 | ||||
| diff --git a/asmcomp/arm/arch.ml b/asmcomp/arm/arch.ml
 | ||||
| index 998fa4b..c4aca8d 100644
 | ||||
| --- a/asmcomp/arm/arch.ml
 | ||||
| +++ b/asmcomp/arm/arch.ml
 | ||||
| @@ -1,25 +1,98 @@
 | ||||
|  (***********************************************************************) | ||||
|  (*                                                                     *) | ||||
| @ -154,7 +181,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/arch.ml ocaml-3.12.1-arm/asmcomp/arm/ar | ||||
|   | ||||
|  (* Addressing modes *) | ||||
|   | ||||
| @@ -37,6 +110,14 @@
 | ||||
| @@ -37,6 +110,14 @@ type specific_operation =
 | ||||
|      Ishiftarith of arith_operation * int | ||||
|    | Ishiftcheckbound of int | ||||
|    | Irevsubimm of int | ||||
| @ -169,7 +196,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/arch.ml ocaml-3.12.1-arm/asmcomp/arm/ar | ||||
|   | ||||
|  and arith_operation = | ||||
|      Ishiftadd | ||||
| @@ -51,6 +132,10 @@
 | ||||
| @@ -51,6 +132,10 @@ let size_addr = 4
 | ||||
|  let size_int = 4 | ||||
|  let size_float = 8 | ||||
|   | ||||
| @ -180,7 +207,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/arch.ml ocaml-3.12.1-arm/asmcomp/arm/ar | ||||
|  (* Operations on addressing modes *) | ||||
|   | ||||
|  let identity_addressing = Iindexed 0 | ||||
| @@ -84,3 +169,56 @@
 | ||||
| @@ -84,3 +169,56 @@ let print_specific_operation printreg op ppf arg =
 | ||||
|        fprintf ppf "check %a >> %i > %a" printreg arg.(0) n printreg arg.(1) | ||||
|    | Irevsubimm n -> | ||||
|        fprintf ppf "%i %s %a" n "-" printreg arg.(0) | ||||
| @ -237,9 +264,10 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/arch.ml ocaml-3.12.1-arm/asmcomp/arm/ar | ||||
| +    s := !s + 2
 | ||||
| +  done;
 | ||||
| +  !s <= m
 | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/emit.mlp
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp	2012-04-27 20:51:07.196775304 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/arm/emit.mlp	2012-04-28 09:20:35.037066348 +0100
 | ||||
| diff --git a/asmcomp/arm/emit.mlp b/asmcomp/arm/emit.mlp
 | ||||
| index a4b2241..846ee4a 100644
 | ||||
| --- a/asmcomp/arm/emit.mlp
 | ||||
| +++ b/asmcomp/arm/emit.mlp
 | ||||
| @@ -1,16 +1,17 @@
 | ||||
|  (***********************************************************************) | ||||
|  (*                                                                     *) | ||||
| @ -264,7 +292,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|   | ||||
|  (* Emission of ARM assembly code *) | ||||
|   | ||||
| @@ -33,16 +34,28 @@
 | ||||
| @@ -33,16 +34,28 @@ let fastcode_flag = ref true
 | ||||
|  let emit_label lbl = | ||||
|    emit_string ".L"; emit_int lbl | ||||
|   | ||||
| @ -297,7 +325,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|    | _ -> fatal_error "Emit_arm.emit_reg" | ||||
|   | ||||
|  (* Layout of the stack frame *) | ||||
| @@ -53,14 +66,23 @@
 | ||||
| @@ -53,14 +66,23 @@ let frame_size () =
 | ||||
|    let sz = | ||||
|      !stack_offset + | ||||
|      4 * num_stack_slots.(0) + | ||||
| @ -324,7 +352,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|   | ||||
|  (* Output a stack reference *) | ||||
|   | ||||
| @@ -79,20 +101,13 @@
 | ||||
| @@ -79,20 +101,13 @@ let emit_addressing addr r n =
 | ||||
|   | ||||
|  (* Record live pointers at call points *) | ||||
|   | ||||
| @ -347,12 +375,22 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|        | {typ = Addr; loc = Stack s} as reg -> | ||||
|            live_offset := slot_offset s (register_class reg) :: !live_offset | ||||
|        | _ -> ()) | ||||
| @@ -100,18 +115,57 @@
 | ||||
| @@ -100,18 +115,57 @@ let record_frame live =
 | ||||
|    frame_descriptors := | ||||
|      { fd_lbl = lbl; | ||||
|        fd_frame_size = frame_size(); | ||||
| -      fd_live_offset = !live_offset } :: !frame_descriptors;
 | ||||
| -  `{emit_label lbl}:`
 | ||||
| -
 | ||||
| -let emit_frame fd =
 | ||||
| -  `	.word	{emit_label fd.fd_lbl} + 4\n`;
 | ||||
| -  `	.short	{emit_int fd.fd_frame_size}\n`;
 | ||||
| -  `	.short	{emit_int (List.length fd.fd_live_offset)}\n`;
 | ||||
| -  List.iter
 | ||||
| -    (fun n ->
 | ||||
| -      `	.short	{emit_int n}\n`)
 | ||||
| -    fd.fd_live_offset;
 | ||||
| -  `	.align	2\n`
 | ||||
| +      fd_live_offset = !live_offset;
 | ||||
| +      fd_debuginfo = dbg } :: !frame_descriptors;
 | ||||
| +  lbl
 | ||||
| @ -394,16 +432,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
| +  end else begin
 | ||||
| +    let bd = List.hd !bound_error_sites in bd.bd_lbl
 | ||||
| +  end
 | ||||
|   | ||||
| -let emit_frame fd =
 | ||||
| -  `	.word	{emit_label fd.fd_lbl} + 4\n`;
 | ||||
| -  `	.short	{emit_int fd.fd_frame_size}\n`;
 | ||||
| -  `	.short	{emit_int (List.length fd.fd_live_offset)}\n`;
 | ||||
| -  List.iter
 | ||||
| -    (fun n ->
 | ||||
| -      `	.short	{emit_int n}\n`)
 | ||||
| -    fd.fd_live_offset;
 | ||||
| -  `	.align	2\n`
 | ||||
| +
 | ||||
| +let emit_call_bound_error bd =
 | ||||
| +  `{emit_label bd.bd_lbl}:	{emit_call "caml_ml_array_bound_error"}\n`;
 | ||||
| +  `{emit_label bd.bd_frame_lbl}:\n`
 | ||||
| @ -416,7 +445,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|   | ||||
|  (* Names of various instructions *) | ||||
|   | ||||
| @@ -121,22 +175,13 @@
 | ||||
| @@ -121,22 +175,13 @@ let name_for_comparison = function
 | ||||
|    | Iunsigned Ceq -> "eq" | Iunsigned Cne -> "ne" | Iunsigned Cle -> "ls" | ||||
|    | Iunsigned Cge -> "cs" | Iunsigned Clt -> "cc" | Iunsigned Cgt -> "hi" | ||||
|   | ||||
| @ -442,7 +471,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|    | _ -> assert false | ||||
|   | ||||
|  let name_for_shift_operation = function | ||||
| @@ -145,60 +190,54 @@
 | ||||
| @@ -145,60 +190,54 @@ let name_for_shift_operation = function
 | ||||
|    | Iasr -> "asr" | ||||
|    | _ -> assert false | ||||
|   | ||||
| @ -529,7 +558,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|          first := false) | ||||
|    end | ||||
|   | ||||
| @@ -206,46 +245,105 @@
 | ||||
| @@ -206,46 +245,105 @@ let emit_intconst r n =
 | ||||
|   | ||||
|  let emit_stack_adjustment instr n = | ||||
|    if n <= 0 then 0 else | ||||
| @ -573,13 +602,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|      lbl | ||||
|   | ||||
| -(* Emit all pending constants *)
 | ||||
| +(* Label a GOTREL literal *)
 | ||||
| +let gotrel_literal l =
 | ||||
| +  let lbl = new_label() in
 | ||||
| +  num_literals := !num_literals + 1;
 | ||||
| +  gotrel_literals := (l, lbl) :: !gotrel_literals;
 | ||||
| +  lbl
 | ||||
|   | ||||
| -
 | ||||
| -let emit_constants () =
 | ||||
| -  Hashtbl.iter
 | ||||
| -    (fun s lbl ->
 | ||||
| @ -591,6 +614,13 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
| -    float_constants;
 | ||||
| -  Hashtbl.clear symbol_constants;
 | ||||
| -  Hashtbl.clear float_constants;
 | ||||
| +(* Label a GOTREL literal *)
 | ||||
| +let gotrel_literal l =
 | ||||
| +  let lbl = new_label() in
 | ||||
| +  num_literals := !num_literals + 1;
 | ||||
| +  gotrel_literals := (l, lbl) :: !gotrel_literals;
 | ||||
| +  lbl
 | ||||
| +
 | ||||
| +(* Label a symbol literal *)
 | ||||
| +let symbol_literal s =
 | ||||
| +  try
 | ||||
| @ -659,7 +689,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|  (* Output the assembly code for an instruction *) | ||||
|   | ||||
|  let emit_instr i = | ||||
| @@ -254,40 +352,76 @@
 | ||||
| @@ -254,40 +352,76 @@ let emit_instr i =
 | ||||
|      | Lop(Imove | Ispill | Ireload) -> | ||||
|          let src = i.arg.(0) and dst = i.res.(0) in | ||||
|          if src.loc = dst.loc then 0 else begin | ||||
| @ -760,7 +790,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|      | Lop(Itailcall_ind) -> | ||||
|          let n = frame_size() in | ||||
|          if !contains_calls then | ||||
| @@ -303,17 +437,16 @@
 | ||||
| @@ -303,17 +437,16 @@ let emit_instr i =
 | ||||
|            if !contains_calls then | ||||
|              `	ldr	lr, [sp, #{emit_int (n-4)}]\n`; | ||||
|            let ninstr = emit_stack_adjustment "add" n in | ||||
| @ -786,7 +816,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|      | Lop(Istackoffset n) -> | ||||
|          assert (n mod 8 = 0); | ||||
|          let ninstr = | ||||
| @@ -322,16 +455,28 @@
 | ||||
| @@ -322,16 +455,28 @@ let emit_instr i =
 | ||||
|            else emit_stack_adjustment "add" (-n) in | ||||
|          stack_offset := !stack_offset + n; | ||||
|          ninstr | ||||
| @ -825,7 +855,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|      | Lop(Iload(size, addr)) -> | ||||
|          let r = i.res.(0) in | ||||
|          let instr = | ||||
| @@ -340,65 +485,114 @@
 | ||||
| @@ -340,65 +485,114 @@ let emit_instr i =
 | ||||
|            | Byte_signed -> "ldrsb" | ||||
|            | Sixteen_unsigned -> "ldrh" | ||||
|            | Sixteen_signed -> "ldrsh" | ||||
| @ -971,7 +1001,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|      | Lop(Iintop_imm(Imod, n)) -> (* n is a power of 2 *) | ||||
|          let l = Misc.log2 n in | ||||
|          let a = i.arg.(0) in | ||||
| @@ -409,40 +603,71 @@
 | ||||
| @@ -409,40 +603,71 @@ let emit_instr i =
 | ||||
|          `	mov	{emit_reg r}, {emit_reg r}, lsr #{emit_int (32-l)}\n`; | ||||
|          `	bpl	{emit_label lbl}\n`; | ||||
|          `	cmp	{emit_reg r}, #0\n`; | ||||
| @ -1064,7 +1094,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|      | Lreloadretaddr -> | ||||
|          let n = frame_size() in | ||||
|          `	ldr	lr, [sp, #{emit_int(n-4)}]\n`; 1 | ||||
| @@ -458,29 +683,41 @@
 | ||||
| @@ -458,29 +683,41 @@ let emit_instr i =
 | ||||
|          begin match tst with | ||||
|            Itruetest -> | ||||
|              `	cmp	{emit_reg i.arg.(0)}, #0\n`; | ||||
| @ -1116,7 +1146,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|          `	cmp	{emit_reg i.arg.(0)}, #1\n`; | ||||
|          begin match lbl0 with | ||||
|            None -> () | ||||
| @@ -495,108 +732,135 @@
 | ||||
| @@ -495,108 +732,135 @@ let emit_instr i =
 | ||||
|          | Some lbl -> `	bgt	{emit_label lbl}\n` | ||||
|          end; | ||||
|          4 | ||||
| @ -1309,7 +1339,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
|   | ||||
|  let data l = | ||||
|    `	.data\n`; | ||||
| @@ -605,32 +869,62 @@
 | ||||
| @@ -605,32 +869,62 @@ let data l =
 | ||||
|  (* Beginning / end of an assembly file *) | ||||
|   | ||||
|  let begin_assembly() = | ||||
| @ -1385,9 +1415,10 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/emit.mlp ocaml-3.12.1-arm/asmcomp/arm/e | ||||
| +      `	.section	.note.GNU-stack,\"\",%progbits\n`
 | ||||
| +  | _ -> ()
 | ||||
| +  end
 | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/proc.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/arm/proc.ml	2009-05-04 14:46:46.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/arm/proc.ml	2012-04-28 09:20:35.055066672 +0100
 | ||||
| diff --git a/asmcomp/arm/proc.ml b/asmcomp/arm/proc.ml
 | ||||
| index e56ac6e..aed2b01 100644
 | ||||
| --- a/asmcomp/arm/proc.ml
 | ||||
| +++ b/asmcomp/arm/proc.ml
 | ||||
| @@ -1,16 +1,17 @@
 | ||||
|  (***********************************************************************) | ||||
|  (*                                                                     *) | ||||
| @ -1412,7 +1443,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
|   | ||||
|  (* Description of the ARM processor *) | ||||
|   | ||||
| @@ -26,32 +27,56 @@
 | ||||
| @@ -26,32 +27,56 @@ let word_addressed = false
 | ||||
|   | ||||
|  (* Registers available for register allocation *) | ||||
|   | ||||
| @ -1449,8 +1480,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
| -|]
 | ||||
| +let int_reg_name =
 | ||||
| +  [| "r0"; "r1"; "r2"; "r3"; "r4"; "r5"; "r6"; "r7"; "r12" |]
 | ||||
|   | ||||
| -let num_register_classes = 1
 | ||||
| +
 | ||||
| +let float_reg_name =
 | ||||
| +  [| "d0";  "d1";  "d2";  "d3";  "d4";  "d5";  "d6";  "d7";
 | ||||
| +     "d8";  "d9";  "d10"; "d11"; "d12"; "d13"; "d14"; "d15";
 | ||||
| @ -1464,7 +1494,8 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
| +   This way we can choose between VFPv3-D16 and VFPv3
 | ||||
| +   at (ocamlopt) runtime using command line switches.
 | ||||
| +*)
 | ||||
| +
 | ||||
|   | ||||
| -let num_register_classes = 1
 | ||||
| +let num_register_classes = 3
 | ||||
|   | ||||
| -let register_class r = assert (r.typ <> Float); 0
 | ||||
| @ -1488,7 +1519,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
|   | ||||
|  let rotate_registers = true | ||||
|   | ||||
| @@ -59,25 +84,34 @@
 | ||||
| @@ -59,25 +84,34 @@ let rotate_registers = true
 | ||||
|   | ||||
|  let hard_int_reg = | ||||
|    let v = Array.create 9 Reg.dummy in | ||||
| @ -1496,16 +1527,16 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
| +  for i = 0 to 8 do
 | ||||
| +    v.(i) <- Reg.at_location Int (Reg i)
 | ||||
| +  done;
 | ||||
|    v | ||||
|   | ||||
| -let all_phys_regs = hard_int_reg
 | ||||
| +  v
 | ||||
| +
 | ||||
| +let hard_float_reg =
 | ||||
| +  let v = Array.create 32 Reg.dummy in
 | ||||
| +  for i = 0 to 31 do
 | ||||
| +    v.(i) <- Reg.at_location Float (Reg(100 + i))
 | ||||
| +  done;
 | ||||
| +  v
 | ||||
| +
 | ||||
|    v | ||||
|   | ||||
| -let all_phys_regs = hard_int_reg
 | ||||
| +let all_phys_regs =
 | ||||
| +  Array.append hard_int_reg hard_float_reg
 | ||||
|   | ||||
| @ -1531,7 +1562,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
|    let ofs = ref 0 in | ||||
|    for i = 0 to Array.length arg - 1 do | ||||
|      match arg.(i).typ with | ||||
| @@ -90,37 +124,86 @@
 | ||||
| @@ -90,37 +124,86 @@ let calling_conventions first_int last_int make_stack arg =
 | ||||
|            ofs := !ofs + size_int | ||||
|          end | ||||
|      | Float -> | ||||
| @ -1630,7 +1661,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
|    | _ -> [||] | ||||
|   | ||||
|  let destroyed_at_raise = all_phys_regs | ||||
| @@ -128,15 +211,16 @@
 | ||||
| @@ -128,15 +211,16 @@ let destroyed_at_raise = all_phys_regs
 | ||||
|  (* Maximal register pressure *) | ||||
|   | ||||
|  let safe_register_pressure = function | ||||
| @ -1651,16 +1682,17 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/proc.ml ocaml-3.12.1-arm/asmcomp/arm/pr | ||||
|  let contains_calls = ref false | ||||
|   | ||||
|  (* Calling the assembler *) | ||||
| @@ -144,6 +228,3 @@
 | ||||
| @@ -144,6 +228,3 @@ let contains_calls = ref false
 | ||||
|  let assemble_file infile outfile = | ||||
|    Ccomp.command (Config.asm ^ " -o " ^ | ||||
|                   Filename.quote outfile ^ " " ^ Filename.quote infile) | ||||
| -
 | ||||
| -open Clflags;;
 | ||||
| -open Config;;
 | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/arm/reload.ml ocaml-3.12.1-arm/asmcomp/arm/reload.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/arm/reload.ml	1999-11-17 18:59:06.000000000 +0000
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/arm/reload.ml	2012-04-28 09:20:35.060066764 +0100
 | ||||
| diff --git a/asmcomp/arm/reload.ml b/asmcomp/arm/reload.ml
 | ||||
| index 0917438..c5b137a 100644
 | ||||
| --- a/asmcomp/arm/reload.ml
 | ||||
| +++ b/asmcomp/arm/reload.ml
 | ||||
| @@ -1,6 +1,6 @@
 | ||||
|  (***********************************************************************) | ||||
|  (*                                                                     *) | ||||
| @ -1678,9 +1710,10 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/reload.ml ocaml-3.12.1-arm/asmcomp/arm/ | ||||
|   | ||||
|  (* Reloading for the ARM *) | ||||
|   | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/arm/scheduling.ml ocaml-3.12.1-arm/asmcomp/arm/scheduling.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/arm/scheduling.ml	1999-11-17 18:59:06.000000000 +0000
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/arm/scheduling.ml	2012-04-28 09:20:35.065066855 +0100
 | ||||
| diff --git a/asmcomp/arm/scheduling.ml b/asmcomp/arm/scheduling.ml
 | ||||
| index 930e1bc..4b47733 100644
 | ||||
| --- a/asmcomp/arm/scheduling.ml
 | ||||
| +++ b/asmcomp/arm/scheduling.ml
 | ||||
| @@ -1,51 +1,79 @@
 | ||||
|  (***********************************************************************) | ||||
|  (*                                                                     *) | ||||
| @ -1787,9 +1820,10 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/scheduling.ml ocaml-3.12.1-arm/asmcomp/ | ||||
|    | _ -> 1 | ||||
|   | ||||
|  end | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/arm/selection.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/arm/selection.ml	2010-04-22 13:39:40.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/arm/selection.ml	2012-04-28 09:20:35.171068774 +0100
 | ||||
| diff --git a/asmcomp/arm/selection.ml b/asmcomp/arm/selection.ml
 | ||||
| index f09d146..94d0367 100644
 | ||||
| --- a/asmcomp/arm/selection.ml
 | ||||
| +++ b/asmcomp/arm/selection.ml
 | ||||
| @@ -1,54 +1,77 @@
 | ||||
|  (***********************************************************************) | ||||
|  (*                                                                     *) | ||||
| @ -1834,25 +1868,6 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
| -  if shift > 22 then false
 | ||||
| -  else if n land (0xFF lsl shift) = n then true
 | ||||
| -  else is_immed n (shift + 2)
 | ||||
| -
 | ||||
| -(* We have 12-bit + sign byte offsets for word accesses,
 | ||||
| -   8-bit + sign word offsets for float accesses,
 | ||||
| -   and 8-bit + sign byte offsets for bytes and shorts.
 | ||||
| -   Use lowest common denominator. *)
 | ||||
| -
 | ||||
| -let is_offset n = n < 256 && n > -256
 | ||||
| -
 | ||||
| -let is_intconst = function Cconst_int n -> true | _ -> false
 | ||||
| -
 | ||||
| -(* Soft emulation of float comparisons *)
 | ||||
| -
 | ||||
| -let float_comparison_function = function
 | ||||
| -  | Ceq -> "__eqdf2"
 | ||||
| -  | Cne -> "__nedf2"
 | ||||
| -  | Clt -> "__ltdf2"
 | ||||
| -  | Cle -> "__ledf2"
 | ||||
| -  | Cgt -> "__gtdf2"
 | ||||
| -  | Cge -> "__gedf2"
 | ||||
| +let is_offset chunk n =
 | ||||
| +  match chunk with
 | ||||
| +  (* VFPv3 load/store have -1020 to 1020 *)
 | ||||
| @ -1871,17 +1886,31 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
| +  (* Everything else has -255 to 255 *)
 | ||||
| +  | _ ->
 | ||||
| +      n >= -255 && n <= 255
 | ||||
| +
 | ||||
|   | ||||
| -(* We have 12-bit + sign byte offsets for word accesses,
 | ||||
| -   8-bit + sign word offsets for float accesses,
 | ||||
| -   and 8-bit + sign byte offsets for bytes and shorts.
 | ||||
| -   Use lowest common denominator. *)
 | ||||
| +let is_intconst = function
 | ||||
| +    Cconst_int _ -> true
 | ||||
| +  | _ -> false
 | ||||
| +
 | ||||
|   | ||||
| -let is_offset n = n < 256 && n > -256
 | ||||
| +(* Special constraints on operand and result registers *)
 | ||||
| +
 | ||||
|   | ||||
| -let is_intconst = function Cconst_int n -> true | _ -> false
 | ||||
| +exception Use_default
 | ||||
| +
 | ||||
|   | ||||
| -(* Soft emulation of float comparisons *)
 | ||||
| +let r1 = phys_reg 1
 | ||||
| +
 | ||||
|   | ||||
| -let float_comparison_function = function
 | ||||
| -  | Ceq -> "__eqdf2"
 | ||||
| -  | Cne -> "__nedf2"
 | ||||
| -  | Clt -> "__ltdf2"
 | ||||
| -  | Cle -> "__ledf2"
 | ||||
| -  | Cgt -> "__gtdf2"
 | ||||
| -  | Cge -> "__gedf2"
 | ||||
| +let pseudoregs_for_operation op arg res =
 | ||||
| +  match op with
 | ||||
| +  (* For mul rd,rm,rs and mla rd,rm,rs,ra (pre-ARMv6) the registers rm
 | ||||
| @ -1906,7 +1935,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
|   | ||||
|  (* Instruction selection *) | ||||
|  class selector = object(self) | ||||
| @@ -56,23 +79,32 @@
 | ||||
| @@ -56,23 +79,32 @@ class selector = object(self)
 | ||||
|  inherit Selectgen.selector_generic as super | ||||
|   | ||||
|  method! regs_for tyv = | ||||
| @ -1933,15 +1962,15 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
|  method is_immediate n = | ||||
| -  n land 0xFF = n || is_immed n 2
 | ||||
| +  is_immediate (Int32.of_int n)
 | ||||
|   | ||||
| -method select_addressing = function
 | ||||
| -    Cop(Cadda, [arg; Cconst_int n]) when is_offset n ->
 | ||||
| +
 | ||||
| +method! is_simple_expr = function
 | ||||
| +  (* inlined floating-point ops are simple if their arguments are *)
 | ||||
| +  | Cop(Cextcall("sqrt", _, _, _), args) when !fpu >= VFPv3_D16 ->
 | ||||
| +      List.for_all self#is_simple_expr args
 | ||||
| +  | e -> super#is_simple_expr e
 | ||||
| +
 | ||||
|   | ||||
| -method select_addressing = function
 | ||||
| -    Cop(Cadda, [arg; Cconst_int n]) when is_offset n ->
 | ||||
| +method select_addressing chunk = function
 | ||||
| +  | Cop(Cadda, [arg; Cconst_int n])
 | ||||
| +    when is_offset chunk n ->
 | ||||
| @ -1952,7 +1981,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
|        (Iindexed n, Cop(Cadda, [arg1; arg2])) | ||||
|    | arg -> | ||||
|        (Iindexed 0, arg) | ||||
| @@ -91,109 +123,146 @@
 | ||||
| @@ -91,109 +123,146 @@ method select_shift_arith op shiftop shiftrevop args =
 | ||||
|    | [Cop(Casr, [arg1; Cconst_int n]); arg2] | ||||
|      when n > 0 && n < 32 && not(is_intconst arg1) -> | ||||
|        (Ispecific(Ishiftarith(shiftrevop, -n)), [arg2; arg1]) | ||||
| @ -2111,7 +2140,8 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
| +        Cop(Cextcall("__aeabi_d2f", typ_int, false, Debuginfo.none),
 | ||||
| +            [arg2]) in
 | ||||
| +      self#select_operation (Cstore Word) [arg1; arg2']
 | ||||
| +  (* Other operations are regular *)
 | ||||
|    (* Other operations are regular *) | ||||
| -  | _ -> super#select_operation op args
 | ||||
| +  | (op, args) -> super#select_operation op args
 | ||||
| +
 | ||||
| +method private select_operation_vfpv3 op args =
 | ||||
| @ -2136,8 +2166,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
| +  (* Recognize floating-point square root *)
 | ||||
| +  | (Cextcall("sqrt", _, false, _), args) ->
 | ||||
| +      (Ispecific Isqrtf, args)
 | ||||
|    (* Other operations are regular *) | ||||
| -  | _ -> super#select_operation op args
 | ||||
| +  (* Other operations are regular *)
 | ||||
| +  | (op, args) -> super#select_operation op args
 | ||||
|   | ||||
|  method! select_condition = function | ||||
| @ -2190,10 +2219,11 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/arm/selection.ml ocaml-3.12.1-arm/asmcomp/a | ||||
|   | ||||
|  end | ||||
|   | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/i386/selection.ml ocaml-3.12.1-arm/asmcomp/i386/selection.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/i386/selection.ml	2010-04-08 04:58:41.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/i386/selection.ml	2012-04-28 12:19:05.529851563 +0100
 | ||||
| @@ -168,7 +168,7 @@
 | ||||
| diff --git a/asmcomp/i386/selection.ml b/asmcomp/i386/selection.ml
 | ||||
| index 1700bf3..827a63d 100644
 | ||||
| --- a/asmcomp/i386/selection.ml
 | ||||
| +++ b/asmcomp/i386/selection.ml
 | ||||
| @@ -168,7 +168,7 @@ method! is_simple_expr e =
 | ||||
|    | _ -> | ||||
|        super#is_simple_expr e | ||||
|   | ||||
| @ -2202,7 +2232,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/i386/selection.ml ocaml-3.12.1-arm/asmcomp/ | ||||
|    match select_addr exp with | ||||
|      (Asymbol s, d) -> | ||||
|        (Ibased(s, d), Ctuple []) | ||||
| @@ -200,7 +200,7 @@
 | ||||
| @@ -200,7 +200,7 @@ method! select_operation op args =
 | ||||
|    match op with | ||||
|    (* Recognize the LEA instruction *) | ||||
|      Caddi | Cadda | Csubi | Csuba -> | ||||
| @ -2211,7 +2241,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/i386/selection.ml ocaml-3.12.1-arm/asmcomp/ | ||||
|          (Iindexed d, _) -> super#select_operation op args | ||||
|        | (Iindexed2 0, _) -> super#select_operation op args | ||||
|        | (addr, arg) -> (Ispecific(Ilea addr), [arg]) | ||||
| @@ -233,7 +233,7 @@
 | ||||
| @@ -233,7 +233,7 @@ method! select_operation op args =
 | ||||
|        begin match args with | ||||
|          [loc; Cop(Caddi, [Cop(Cload _, [loc']); Cconst_int n])] | ||||
|          when loc = loc' -> | ||||
| @ -2220,7 +2250,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/i386/selection.ml ocaml-3.12.1-arm/asmcomp/ | ||||
|            (Ispecific(Ioffset_loc(n, addr)), [arg]) | ||||
|        | _ -> | ||||
|            super#select_operation op args | ||||
| @@ -250,11 +250,11 @@
 | ||||
| @@ -250,11 +250,11 @@ method! select_operation op args =
 | ||||
|  method select_floatarith regular_op reversed_op mem_op mem_rev_op args = | ||||
|    match args with | ||||
|      [arg1; Cop(Cload chunk, [loc2])] -> | ||||
| @ -2234,7 +2264,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/i386/selection.ml ocaml-3.12.1-arm/asmcomp/ | ||||
|        (Ispecific(Ifloatarithmem(chunk_double chunk, mem_rev_op, addr)), | ||||
|                   [arg2; arg1]) | ||||
|    | [arg1; arg2] -> | ||||
| @@ -295,10 +295,10 @@
 | ||||
| @@ -295,10 +295,10 @@ method select_push exp =
 | ||||
|    | Cconst_natpointer n -> (Ispecific(Ipush_int n), Ctuple []) | ||||
|    | Cconst_symbol s -> (Ispecific(Ipush_symbol s), Ctuple []) | ||||
|    | Cop(Cload Word, [loc]) -> | ||||
| @ -2247,10 +2277,11 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/i386/selection.ml ocaml-3.12.1-arm/asmcomp/ | ||||
|        (Ispecific(Ipush_load_float addr), arg) | ||||
|    | _ -> (Ispecific(Ipush), exp) | ||||
|   | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/power/selection.ml ocaml-3.12.1-arm/asmcomp/power/selection.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/power/selection.ml	2010-04-22 13:51:06.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/power/selection.ml	2012-04-28 12:19:05.537851684 +0100
 | ||||
| @@ -52,7 +52,7 @@
 | ||||
| diff --git a/asmcomp/power/selection.ml b/asmcomp/power/selection.ml
 | ||||
| index ed15efb..0532d6b 100644
 | ||||
| --- a/asmcomp/power/selection.ml
 | ||||
| +++ b/asmcomp/power/selection.ml
 | ||||
| @@ -52,7 +52,7 @@ inherit Selectgen.selector_generic as super
 | ||||
|   | ||||
|  method is_immediate n = (n <= 32767) && (n >= -32768) | ||||
|   | ||||
| @ -2259,10 +2290,24 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/power/selection.ml ocaml-3.12.1-arm/asmcomp | ||||
|    match select_addr exp with | ||||
|      (Asymbol s, d) -> | ||||
|        (Ibased(s, d), Ctuple []) | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/selectgen.ml ocaml-3.12.1-arm/asmcomp/selectgen.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/selectgen.ml	2010-09-02 14:29:21.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/selectgen.ml	2012-04-28 12:19:05.538851709 +0100
 | ||||
| @@ -204,7 +204,7 @@
 | ||||
| diff --git a/asmcomp/power64/selection.ml b/asmcomp/power64/selection.ml
 | ||||
| index afc7649..18b5318 100644
 | ||||
| --- a/asmcomp/power64/selection.ml
 | ||||
| +++ b/asmcomp/power64/selection.ml
 | ||||
| @@ -52,7 +52,7 @@ inherit Selectgen.selector_generic as super
 | ||||
|   | ||||
|  method is_immediate n = (n <= 32767) && (n >= -32768) | ||||
|   | ||||
| -method select_addressing exp =
 | ||||
| +method select_addressing chunk exp =
 | ||||
|    match select_addr exp with | ||||
|      (Asymbol s, d) -> | ||||
|        (Ibased(s, d), Ctuple []) | ||||
| diff --git a/asmcomp/selectgen.ml b/asmcomp/selectgen.ml
 | ||||
| index 2fc40f7..0bc9efb 100644
 | ||||
| --- a/asmcomp/selectgen.ml
 | ||||
| +++ b/asmcomp/selectgen.ml
 | ||||
| @@ -204,7 +204,7 @@ method virtual is_immediate : int -> bool
 | ||||
|  (* Selection of addressing modes *) | ||||
|   | ||||
|  method virtual select_addressing : | ||||
| @ -2271,7 +2316,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/selectgen.ml ocaml-3.12.1-arm/asmcomp/selec | ||||
|   | ||||
|  (* Default instruction selection for stores (of words) *) | ||||
|   | ||||
| @@ -219,10 +219,10 @@
 | ||||
| @@ -219,10 +219,10 @@ method select_operation op args =
 | ||||
|    | (Capply(ty, dbg), _) -> (Icall_ind, args) | ||||
|    | (Cextcall(s, ty, alloc, dbg), _) -> (Iextcall(s, alloc), args) | ||||
|    | (Cload chunk, [arg]) -> | ||||
| @ -2284,7 +2329,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/selectgen.ml ocaml-3.12.1-arm/asmcomp/selec | ||||
|        if chunk = Word then begin | ||||
|          let (op, newarg2) = self#select_store addr arg2 in | ||||
|          (op, [newarg2; eloc]) | ||||
| @@ -366,7 +366,7 @@
 | ||||
| @@ -366,7 +366,7 @@ method insert_move src dst =
 | ||||
|      self#insert (Iop Imove) [|src|] [|dst|] | ||||
|   | ||||
|  method insert_moves src dst = | ||||
| @ -2293,7 +2338,7 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/selectgen.ml ocaml-3.12.1-arm/asmcomp/selec | ||||
|      self#insert_move src.(i) dst.(i) | ||||
|    done | ||||
|   | ||||
| @@ -490,9 +490,8 @@
 | ||||
| @@ -490,9 +490,8 @@ method emit_expr env exp =
 | ||||
|                let (loc_arg, stack_ofs) = | ||||
|                  self#emit_extcall_args env new_args in | ||||
|                let rd = self#regs_for ty in | ||||
| @ -2305,10 +2350,11 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/selectgen.ml ocaml-3.12.1-arm/asmcomp/selec | ||||
|                self#insert_move_results loc_res rd stack_ofs; | ||||
|                Some rd | ||||
|            | Ialloc _ -> | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/selectgen.mli ocaml-3.12.1-arm/asmcomp/selectgen.mli
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/selectgen.mli	2010-05-21 13:00:49.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/selectgen.mli	2012-04-28 12:19:05.539851737 +0100
 | ||||
| @@ -26,7 +26,7 @@
 | ||||
| diff --git a/asmcomp/selectgen.mli b/asmcomp/selectgen.mli
 | ||||
| index ae53cda..69dae6d 100644
 | ||||
| --- a/asmcomp/selectgen.mli
 | ||||
| +++ b/asmcomp/selectgen.mli
 | ||||
| @@ -26,7 +26,7 @@ class virtual selector_generic : object
 | ||||
|      (* Must be defined to indicate whether a constant is a suitable | ||||
|         immediate operand to arithmetic instructions *) | ||||
|    method virtual select_addressing : | ||||
| @ -2317,10 +2363,11 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/selectgen.mli ocaml-3.12.1-arm/asmcomp/sele | ||||
|      (* Must be defined to select addressing modes *) | ||||
|    method is_simple_expr: Cmm.expression -> bool | ||||
|      (* Can be overridden to reflect special extcalls known to be pure *) | ||||
| diff -urN ocaml-3.12.1-noarm/asmcomp/sparc/selection.ml ocaml-3.12.1-arm/asmcomp/sparc/selection.ml
 | ||||
| --- ocaml-3.12.1-noarm/asmcomp/sparc/selection.ml	2010-04-22 13:51:06.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmcomp/sparc/selection.ml	2012-04-28 12:19:05.540851767 +0100
 | ||||
| @@ -26,7 +26,7 @@
 | ||||
| diff --git a/asmcomp/sparc/selection.ml b/asmcomp/sparc/selection.ml
 | ||||
| index 82758dc..c1f30fd 100644
 | ||||
| --- a/asmcomp/sparc/selection.ml
 | ||||
| +++ b/asmcomp/sparc/selection.ml
 | ||||
| @@ -26,7 +26,7 @@ inherit Selectgen.selector_generic as super
 | ||||
|   | ||||
|  method is_immediate n = (n <= 4095) && (n >= -4096) | ||||
|   | ||||
| @ -2329,9 +2376,10 @@ diff -urN ocaml-3.12.1-noarm/asmcomp/sparc/selection.ml ocaml-3.12.1-arm/asmcomp | ||||
|      Cconst_symbol s -> | ||||
|        (Ibased(s, 0), Ctuple []) | ||||
|    | Cop(Cadda, [Cconst_symbol s; Cconst_int n]) -> | ||||
| diff -urN ocaml-3.12.1-noarm/asmrun/arm.S ocaml-3.12.1-arm/asmrun/arm.S
 | ||||
| --- ocaml-3.12.1-noarm/asmrun/arm.S	2012-04-27 20:51:07.197775311 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmrun/arm.S	2012-04-28 13:39:34.463111027 +0100
 | ||||
| diff --git a/asmrun/arm.S b/asmrun/arm.S
 | ||||
| index 1313e9c..6482956 100644
 | ||||
| --- a/asmrun/arm.S
 | ||||
| +++ b/asmrun/arm.S
 | ||||
| @@ -1,286 +1,411 @@
 | ||||
|  /***********************************************************************/ | ||||
|  /*                                                                     */ | ||||
| @ -2794,10 +2842,10 @@ diff -urN ocaml-3.12.1-noarm/asmrun/arm.S ocaml-3.12.1-arm/asmrun/arm.S | ||||
| +        .size   .Lcaml_retaddr, .-.Lcaml_retaddr
 | ||||
| +        .type   caml_start_program, %function
 | ||||
| +        .size   caml_start_program, .-caml_start_program
 | ||||
| +
 | ||||
| +/* The trap handler */
 | ||||
|   | ||||
| -    /* The trap handler */
 | ||||
| +/* The trap handler */
 | ||||
| +
 | ||||
| +        .align  2
 | ||||
|  .Ltrap_handler: | ||||
|      /* Save exception pointer */ | ||||
| @ -2934,7 +2982,7 @@ diff -urN ocaml-3.12.1-noarm/asmrun/arm.S ocaml-3.12.1-arm/asmrun/arm.S | ||||
|      /* Initial shuffling of arguments */ | ||||
|      /* (r0 = closure, r1 = arg1, r2 = arg2, r3 = arg3) */ | ||||
|          mov     r12, r0 | ||||
| @@ -288,43 +413,36 @@
 | ||||
| @@ -288,43 +413,36 @@ caml_callback3_exn:
 | ||||
|          mov     r1, r2          /* r1 = second arg */ | ||||
|          mov     r2, r3          /* r2 = third arg */ | ||||
|          mov     r3, r12         /* r3 = closure environment */ | ||||
| @ -2994,9 +3042,10 @@ diff -urN ocaml-3.12.1-noarm/asmrun/arm.S ocaml-3.12.1-arm/asmrun/arm.S | ||||
|          .align  2 | ||||
| +        .type   caml_system__frametable, %object
 | ||||
| +        .size   caml_system__frametable, .-caml_system__frametable
 | ||||
| diff -urN ocaml-3.12.1-noarm/asmrun/signals_osdep.h ocaml-3.12.1-arm/asmrun/signals_osdep.h
 | ||||
| --- ocaml-3.12.1-noarm/asmrun/signals_osdep.h	2009-05-20 12:52:42.000000000 +0100
 | ||||
| +++ ocaml-3.12.1-arm/asmrun/signals_osdep.h	2012-04-28 09:23:12.209919224 +0100
 | ||||
| diff --git a/asmrun/signals_osdep.h b/asmrun/signals_osdep.h
 | ||||
| index 1e91327..732f3a0 100644
 | ||||
| --- a/asmrun/signals_osdep.h
 | ||||
| +++ b/asmrun/signals_osdep.h
 | ||||
| @@ -78,7 +78,7 @@
 | ||||
|   | ||||
|  /****************** ARM, Linux */ | ||||
| @ -3006,10 +3055,11 @@ diff -urN ocaml-3.12.1-noarm/asmrun/signals_osdep.h ocaml-3.12.1-arm/asmrun/sign | ||||
|   | ||||
|    #include <sys/ucontext.h> | ||||
|   | ||||
| diff -urN ocaml-3.12.1-noarm/configure ocaml-3.12.1-arm/configure
 | ||||
| --- ocaml-3.12.1-noarm/configure	2012-04-27 20:51:07.193775283 +0100
 | ||||
| +++ ocaml-3.12.1-arm/configure	2012-04-28 09:23:59.270773673 +0100
 | ||||
| @@ -636,6 +636,7 @@
 | ||||
| diff --git a/configure b/configure
 | ||||
| index 6ed0a9c..4e07c92 100755
 | ||||
| --- a/configure
 | ||||
| +++ b/configure
 | ||||
| @@ -636,6 +636,7 @@ if test $withsharedlibs = "yes"; then
 | ||||
|      i[345]86-*-netbsd*)           natdynlink=true;; | ||||
|      x86_64-*-netbsd*)             natdynlink=true;; | ||||
|      i386-*-gnu0.3)                natdynlink=true;; | ||||
| @ -3017,7 +3067,7 @@ diff -urN ocaml-3.12.1-noarm/configure ocaml-3.12.1-arm/configure | ||||
|    esac | ||||
|  fi | ||||
|   | ||||
| @@ -690,8 +691,13 @@
 | ||||
| @@ -691,8 +692,13 @@ case "$host" in
 | ||||
|    powerpc-*-rhapsody*)          arch=power; model=ppc; system=rhapsody;; | ||||
|    powerpc-*-darwin*)            arch=power; system=rhapsody | ||||
|                                  if $arch64; then model=ppc64; else model=ppc; fi;; | ||||
| @ -3033,7 +3083,7 @@ diff -urN ocaml-3.12.1-noarm/configure ocaml-3.12.1-arm/configure | ||||
|    ia64-*-linux*)                arch=ia64; system=linux;; | ||||
|    ia64-*-gnu*)                  arch=ia64; system=gnu;; | ||||
|    ia64-*-freebsd*)              arch=ia64; system=freebsd;; | ||||
| @@ -801,6 +807,7 @@
 | ||||
| @@ -804,6 +810,7 @@ case "$arch,$model,$system" in
 | ||||
|      case "$nativecc" in gcc*) ;; *) cc_profile='-xpg';; esac;; | ||||
|    amd64,*,linux) profiling='prof';; | ||||
|    amd64,*,gnu) profiling='prof';; | ||||
| @ -3041,3 +3091,6 @@ diff -urN ocaml-3.12.1-noarm/configure ocaml-3.12.1-arm/configure | ||||
|    *) profiling='noprof';; | ||||
|  esac | ||||
|   | ||||
| -- 
 | ||||
| 1.7.10 | ||||
| 
 | ||||
							
								
								
									
										1522
									
								
								config.guess
									
									
									
									
										vendored
									
									
								
							
							
						
						
									
										1522
									
								
								config.guess
									
									
									
									
										vendored
									
									
								
							
										
											
												File diff suppressed because it is too large
												Load Diff
											
										
									
								
							
							
								
								
									
										1771
									
								
								config.sub
									
									
									
									
										vendored
									
									
								
							
							
						
						
									
										1771
									
								
								config.sub
									
									
									
									
										vendored
									
									
								
							
										
											
												File diff suppressed because it is too large
												Load Diff
											
										
									
								
							| @ -1,12 +0,0 @@ | ||||
| diff -up ocaml-3.12.1/asmcomp/power64/selection.ml.ppc_1 ocaml-3.12.1/asmcomp/power64/selection.ml
 | ||||
| --- ocaml-3.12.1/asmcomp/power64/selection.ml.ppc_1	2012-05-15 15:28:45.240364647 +0200
 | ||||
| +++ ocaml-3.12.1/asmcomp/power64/selection.ml	2012-05-15 15:28:58.170366764 +0200
 | ||||
| @@ -52,7 +52,7 @@ inherit Selectgen.selector_generic as su
 | ||||
|   | ||||
|  method is_immediate n = (n <= 32767) && (n >= -32768) | ||||
|   | ||||
| -method select_addressing exp =
 | ||||
| +method select_addressing chunk exp =
 | ||||
|    match select_addr exp with | ||||
|      (Asymbol s, d) -> | ||||
|        (Ibased(s, d), Ctuple []) | ||||
| @ -1,13 +0,0 @@ | ||||
| diff -ur ocaml-3.12.0.old/tools/Makefile.shared ocaml-3.12.0/tools/Makefile.shared
 | ||||
| --- ocaml-3.12.0.old/tools/Makefile.shared	2010-06-07 07:58:41.000000000 +0100
 | ||||
| +++ ocaml-3.12.0/tools/Makefile.shared	2011-01-04 21:56:13.023974253 +0000
 | ||||
| @@ -108,9 +108,6 @@
 | ||||
|  	sed -e "s|%%BINDIR%%|$(BINDIR)|" \ | ||||
|  	    -e "s|%%SUPPORTS_SHARED_LIBRARIES%%|$(SUPPORTS_SHARED_LIBRARIES)|" \ | ||||
|  	    -e "s|%%MKSHAREDLIB%%|$(MKSHAREDLIB)|" \ | ||||
| -	    -e "s|%%BYTECCRPATH%%|$(BYTECCRPATH)|" \
 | ||||
| -	    -e "s|%%NATIVECCRPATH%%|$(NATIVECCRPATH)|" \
 | ||||
| -	    -e "s|%%MKSHAREDLIBRPATH%%|$(MKSHAREDLIBRPATH)|" \
 | ||||
|  	    -e "s|%%RANLIB%%|$(RANLIB)|" \ | ||||
|  	  ocamlmklib.mlp >> ocamlmklib.ml | ||||
|   | ||||
| @ -1,12 +0,0 @@ | ||||
| --- ocaml-3.10.0/tools/Makefile.rpath	2007-06-02 16:53:10.000000000 +0200
 | ||||
| +++ ocaml-3.10.0/tools/Makefile	2007-06-02 16:53:28.000000000 +0200
 | ||||
| @@ -107,9 +107,6 @@
 | ||||
|  	sed -e "s|%%BINDIR%%|$(BINDIR)|" \ | ||||
|              -e "s|%%SUPPORTS_SHARED_LIBRARIES%%|$(SUPPORTS_SHARED_LIBRARIES)|" \ | ||||
|              -e "s|%%MKSHAREDLIB%%|$(MKSHAREDLIB)|" \ | ||||
| -            -e "s|%%BYTECCRPATH%%|$(BYTECCRPATH)|" \
 | ||||
| -            -e "s|%%NATIVECCRPATH%%|$(NATIVECCRPATH)|" \
 | ||||
| -            -e "s|%%MKSHAREDLIBRPATH%%|$(MKSHAREDLIBRPATH)|" \
 | ||||
|              -e "s|%%RANLIB%%|$(RANLIB)|" \ | ||||
|            ocamlmklib.mlp >> ocamlmklib.ml | ||||
|   | ||||
| @ -1,13 +0,0 @@ | ||||
| --- ocaml-3.10.0/configure.opt	2007-06-02 16:50:12.000000000 +0200
 | ||||
| +++ ocaml-3.10.0/configure	2007-06-02 16:50:34.000000000 +0200
 | ||||
| @@ -1425,6 +1425,10 @@
 | ||||
|      nativecccompopts="$nativecccompopts -fomit-frame-pointer";; | ||||
|  esac | ||||
|   | ||||
| +# Allow user defined C Compiler flags
 | ||||
| +bytecccompopts="$bytecccompopts $CFLAGS"
 | ||||
| +nativecccompopts="$nativecccompopts $CFLAGS"
 | ||||
| +
 | ||||
|  # Finish generated files | ||||
|   | ||||
|  cclibs="$cclibs $mathlib" | ||||
							
								
								
									
										72
									
								
								ocaml.spec
									
									
									
									
									
								
							
							
						
						
									
										72
									
								
								ocaml.spec
									
									
									
									
									
								
							| @ -2,7 +2,7 @@ | ||||
| 
 | ||||
| Name:           ocaml | ||||
| Version:        3.12.1 | ||||
| Release:        4%{?dist} | ||||
| Release:        5%{?dist} | ||||
| 
 | ||||
| Summary:        Objective Caml compiler and programming environment | ||||
| 
 | ||||
| @ -16,32 +16,26 @@ Source1:        http://caml.inria.fr/distrib/ocaml-3.12/ocaml-3.12-refman.html.t | ||||
| Source2:        http://caml.inria.fr/distrib/ocaml-3.12/ocaml-3.12-refman.pdf | ||||
| Source3:        http://caml.inria.fr/distrib/ocaml-3.12/ocaml-3.12-refman.info.tar.gz | ||||
| 
 | ||||
| # Useful utilities from Debian, and sent upstream. | ||||
| # http://git.debian.org/?p=pkg-ocaml-maint/packages/ocaml.git;a=tree;f=debian/ocamlbyteinfo;hb=HEAD | ||||
| Source6:        ocamlbyteinfo.ml | ||||
| #Source7:        ocamlplugininfo.ml | ||||
| 
 | ||||
| # GNU config.guess and config.sub supplied with OCaml are 8 years old. | ||||
| # Use newer versions. | ||||
| Source8:        config.guess | ||||
| Source9:        config.sub | ||||
| 
 | ||||
| Patch0:         ocaml-3.12.0-rpath.patch | ||||
| Patch1:         ocaml-user-cflags.patch | ||||
| 
 | ||||
| # Patch from Debian for ARM (sent upstream). | ||||
| Patch3:         debian_patches_0013-ocamlopt-arm-add-.type-directive-for-code-symbols.patch | ||||
| 
 | ||||
| # Non-upstream patch to build on ppc64. | ||||
| Patch4:         ocaml-ppc64.patch | ||||
| 
 | ||||
| # New ARM backend by Benedikt Meurer (PR#5433), backported to OCaml 3.12.1. | ||||
| Patch5:         ocaml-3.12.1-merge-the-new-ARM-backend-into-trunk-PR-5433.patch | ||||
| 
 | ||||
| # the new arm backend missed one small patch for PPC: | ||||
| Patch6:		ocaml-3.12-ppc.patch | ||||
| 
 | ||||
| BuildRoot:      %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) | ||||
| # IMPORTANT NOTE: | ||||
| # | ||||
| # These patches are generated from unpacked sources stored in a | ||||
| # fedorahosted git repository.  If you change the patches here, they | ||||
| # will be OVERWRITTEN by the next update.  Instead, request commit | ||||
| # access to the fedorahosted project: | ||||
| # | ||||
| # http://git.fedorahosted.org/git/?p=fedora-ocaml.git | ||||
| # | ||||
| # ALTERNATIVELY add a patch to the end of the list (leaving the | ||||
| # existing patches unchanged) adding a comment to note that it should | ||||
| # be incorporated into the git repo at a later time. | ||||
| # | ||||
| Patch0001:      0001-ocamlbyteinfo-ocamlplugininfo-Useful-utilities-from-.patch | ||||
| Patch0002:      0002-GNU-config.guess-and-config.sub-replacements.patch | ||||
| Patch0003:      0003-Don-t-add-rpaths-to-libraries.patch | ||||
| Patch0004:      0004-configure-Allow-user-defined-C-compiler-flags.patch | ||||
| Patch0005:      0005-ocamlopt-arm-add-.type-directive-for-code-symbols.patch | ||||
| Patch0006:      0006-Add-support-for-ppc64.patch | ||||
| Patch0007:      0007-New-ARM-backend-written-by-Benedikt-Meurer-PR-5433.patch | ||||
| 
 | ||||
| # Depend on previous version of OCaml so that ocamlobjinfo | ||||
| # can run. | ||||
| @ -230,18 +224,16 @@ man pages and info files. | ||||
| %setup -q -T -b 0 -n %{name}-%{version} | ||||
| %setup -q -T -D -a 1 -n %{name}-%{version} | ||||
| %setup -q -T -D -a 3 -n %{name}-%{version} | ||||
| %patch0 -p1 -b .rpath | ||||
| %patch1 -p1 -b .cflags | ||||
| %patch3 -p1 -b .arm-type-dir | ||||
| %ifarch ppc ppc64 | ||||
| %patch4 -p1 -b .ppc64 | ||||
| %patch6 -p1 -b .ppc64_1 | ||||
| %endif | ||||
| %patch5 -p1 -b .new-arm | ||||
| 
 | ||||
| git init | ||||
| git config user.email "noone@example.com" | ||||
| git config user.name "no one" | ||||
| git add . | ||||
| git commit -a -q -m "%{version} baseline" | ||||
| git am %{patches} | ||||
| 
 | ||||
| cp %{SOURCE2} refman.pdf | ||||
| 
 | ||||
| cp %{SOURCE8} %{SOURCE9} config/gnu/ | ||||
| chmod +x config/gnu/config.{guess,sub} | ||||
| 
 | ||||
| 
 | ||||
| @ -261,7 +253,6 @@ make -C emacs ocamltags | ||||
| 
 | ||||
| # Currently these tools are supplied by Debian, but are expected | ||||
| # to go upstream at some point. | ||||
| cp %{SOURCE6} . | ||||
| includes="-nostdlib -I stdlib -I utils -I parsing -I typing -I bytecomp -I asmcomp -I driver -I otherlibs/unix -I otherlibs/str -I otherlibs/dynlink" | ||||
| boot/ocamlrun ./ocamlc $includes dynlinkaux.cmo ocamlbyteinfo.ml -o ocamlbyteinfo | ||||
| #cp otherlibs/dynlink/natdynlink.ml . | ||||
| @ -508,7 +499,12 @@ fi | ||||
| 
 | ||||
| 
 | ||||
| %changelog | ||||
| * Tue May 15 2012 Tue May 15 2012 Karsten Hopp <karsten@redhat.com> 3.12.1-4 | ||||
| * Tue May 29 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-5 | ||||
| - Move patches to external git repo: | ||||
|   http://git.fedorahosted.org/git/?p=fedora-ocaml.git | ||||
|   There should be no change introduced here. | ||||
| 
 | ||||
| * Tue May 15 2012 Karsten Hopp <karsten@redhat.com> 3.12.1-4 | ||||
| - ppc64 got broken by the new ARM backend, add a minor patch | ||||
| 
 | ||||
| * Sat Apr 28 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-3 | ||||
|  | ||||
							
								
								
									
										101
									
								
								ocamlbyteinfo.ml
									
									
									
									
									
								
							
							
						
						
									
										101
									
								
								ocamlbyteinfo.ml
									
									
									
									
									
								
							| @ -1,101 +0,0 @@ | ||||
| (***********************************************************************) | ||||
| (*                                                                     *) | ||||
| (*                           Objective Caml                            *) | ||||
| (*                                                                     *) | ||||
| (*            Xavier Leroy, projet Gallium, INRIA Rocquencourt         *) | ||||
| (*                                                                     *) | ||||
| (*  Copyright 2009 Institut National de Recherche en Informatique et   *) | ||||
| (*  en Automatique.  All rights reserved.  This file is distributed    *) | ||||
| (*  under the terms of the GNU Library General Public License, with    *) | ||||
| (*  the special exception on linking described in file ../../LICENSE.  *) | ||||
| (*                                                                     *) | ||||
| (***********************************************************************) | ||||
| 
 | ||||
| (* $Id$ *) | ||||
| 
 | ||||
| (* Dumps a bytecode binary file *) | ||||
| 
 | ||||
| open Sys | ||||
| open Dynlinkaux | ||||
| 
 | ||||
| let input_stringlist ic len = | ||||
|   let get_string_list sect len = | ||||
|     let rec fold s e acc = | ||||
|       if e != len then | ||||
|         if sect.[e] = '\000' then | ||||
|           fold (e+1) (e+1) (String.sub sect s (e-s) :: acc) | ||||
|         else fold s (e+1) acc | ||||
|       else acc | ||||
|     in fold 0 0 [] | ||||
|   in | ||||
|   let sect = String.create len in | ||||
|   let _ = really_input ic sect 0 len in | ||||
|   get_string_list sect len | ||||
| 
 | ||||
| let print = Printf.printf | ||||
| let perr s = | ||||
|   Printf.eprintf "%s\n" s; | ||||
|   exit(1) | ||||
| let p_title title = print "%s:\n" title | ||||
| 
 | ||||
| let p_section title format pdata = function | ||||
|   | [] -> () | ||||
|   | l -> | ||||
|       p_title title; | ||||
|       List.iter | ||||
|         (fun (name, data) -> print format (pdata data) name) | ||||
|         l | ||||
| 
 | ||||
| let p_list title format = function | ||||
|   | [] -> () | ||||
|   | l -> | ||||
|       p_title title; | ||||
|       List.iter | ||||
|         (fun name -> print format name) | ||||
|         l | ||||
| 
 | ||||
| let _ = | ||||
|   try | ||||
|     let input_name = Sys.argv.(1) in | ||||
|     let ic = open_in_bin input_name in | ||||
|     Bytesections.read_toc ic; | ||||
|     List.iter | ||||
|       (fun section -> | ||||
|          try | ||||
|            let len = Bytesections.seek_section ic section in | ||||
|            if len > 0 then match section with | ||||
|              | "CRCS" -> | ||||
|                  p_section | ||||
|                    "Imported Units" | ||||
|                    "\t%s\t%s\n" | ||||
|                    Digest.to_hex | ||||
|                    (input_value ic : (string * Digest.t) list) | ||||
|              | "DLLS" -> | ||||
|                  p_list | ||||
|                    "Used Dlls" "\t%s\n" | ||||
|                    (input_stringlist ic len) | ||||
|              | "DLPT" -> | ||||
|                  p_list | ||||
|                    "Additional Dll paths" | ||||
|                    "\t%s\n" | ||||
|                    (input_stringlist ic len) | ||||
|              | "PRIM" -> | ||||
|                  let prims = (input_stringlist ic len) in | ||||
|                  print "Uses unsafe features: "; | ||||
|                  begin match prims with | ||||
|                      [] -> print "no\n" | ||||
|                    | l  -> print "YES\n"; | ||||
|                        p_list "Primitives declared in this module" | ||||
|                          "\t%s\n" | ||||
|                          l | ||||
|                  end | ||||
|              | _ -> () | ||||
|          with Not_found | Failure _ | Invalid_argument _ -> () | ||||
|       ) | ||||
|       ["CRCS"; "DLLS"; "DLPT"; "PRIM"]; | ||||
|     close_in ic | ||||
|   with | ||||
|     | Sys_error msg -> | ||||
|         perr msg | ||||
|     | Invalid_argument("index out of bounds") -> | ||||
|         perr (Printf.sprintf "Usage: %s filename" Sys.argv.(0)) | ||||
| @ -1,109 +0,0 @@ | ||||
| (***********************************************************************) | ||||
| (*                                                                     *) | ||||
| (*                           Objective Caml                            *) | ||||
| (*                                                                     *) | ||||
| (*            Xavier Leroy, projet Gallium, INRIA Rocquencourt         *) | ||||
| (*                                                                     *) | ||||
| (*  Copyright 2009 Institut National de Recherche en Informatique et   *) | ||||
| (*  en Automatique.  All rights reserved.  This file is distributed    *) | ||||
| (*  under the terms of the GNU Library General Public License, with    *) | ||||
| (*  the special exception on linking described in file ../../LICENSE.  *) | ||||
| (*                                                                     *) | ||||
| (***********************************************************************) | ||||
| 
 | ||||
| (* $Id$ *) | ||||
| 
 | ||||
| (* Dumps a .cmxs file *) | ||||
| 
 | ||||
| open Natdynlink | ||||
| open Format | ||||
| 
 | ||||
| let file = | ||||
|   try | ||||
|     Sys.argv.(1) | ||||
|   with _ -> begin | ||||
|     Printf.eprintf "Usage: %s file.cmxs\n" Sys.argv.(0); | ||||
|     exit(1) | ||||
|   end | ||||
| 
 | ||||
| exception Abnormal_exit | ||||
| 
 | ||||
| let error s e = | ||||
|   let eprint = Printf.eprintf in | ||||
|   let print_exc s = function | ||||
|     | End_of_file -> | ||||
|        eprint "%s: %s\n" s file | ||||
|     | Abnormal_exit -> | ||||
|         eprint "%s\n" s | ||||
|     | e -> eprint "%s\n" (Printexc.to_string e) | ||||
|   in | ||||
|     print_exc s e; | ||||
|     exit(1) | ||||
| 
 | ||||
| let read_in command = | ||||
|   let cmd = Printf.sprintf command file in | ||||
|   let ic = Unix.open_process_in cmd in | ||||
|   try | ||||
|     let line = input_line ic in | ||||
|     begin match (Unix.close_process_in ic) with | ||||
|       | Unix.WEXITED 0 -> Str.split (Str.regexp "[ ]+") line | ||||
|       | Unix.WEXITED _  | Unix.WSIGNALED _ | Unix.WSTOPPED _ -> | ||||
|           error | ||||
|             (Printf.sprintf | ||||
|                "Command \"%s\" exited abnormally" | ||||
|                cmd | ||||
|             ) | ||||
|             Abnormal_exit | ||||
|     end | ||||
|   with e -> error "File is empty" e | ||||
| 
 | ||||
| let get_offset adr_off adr_sec = | ||||
|   try | ||||
|     let adr = List.nth adr_off 4 in | ||||
|     let off = List.nth adr_off 5 in | ||||
|     let sec = List.hd adr_sec in | ||||
| 
 | ||||
|     let (!) x = Int64.of_string ("0x" ^ x) in | ||||
|     let (+) = Int64.add in | ||||
|     let (-) = Int64.sub in | ||||
| 
 | ||||
|       Int64.to_int (!off + !sec - !adr) | ||||
| 
 | ||||
|   with Failure _ | Invalid_argument _ -> | ||||
|     error | ||||
|       "Command output doesn't have the expected format" | ||||
|       Abnormal_exit | ||||
| 
 | ||||
| let print_infos name crc defines cmi cmx = | ||||
|   let print_name_crc (name, crc) = | ||||
|     printf "@ %s (%s)" name (Digest.to_hex crc) | ||||
|   in | ||||
|   let pr_imports ppf imps = List.iter print_name_crc imps in | ||||
|   printf "Name: %s@." name; | ||||
|   printf "CRC of implementation: %s@." (Digest.to_hex crc); | ||||
|   printf "@[<hov 2>Globals defined:"; | ||||
|   List.iter (fun s -> printf "@ %s" s) defines; | ||||
|   printf "@]@."; | ||||
|   printf "@[<v 2>Interfaces imported:%a@]@." pr_imports cmi; | ||||
|   printf "@[<v 2>Implementations imported:%a@]@." pr_imports cmx | ||||
| 
 | ||||
| let _ = | ||||
|   let adr_off = read_in "objdump -h %s | grep ' .data '" in | ||||
|   let adr_sec = read_in "objdump -T %s | grep ' caml_plugin_header$'" in | ||||
| 
 | ||||
|   let ic = open_in file in | ||||
|   let _ = seek_in ic (get_offset adr_off adr_sec) in | ||||
|   let header  = (input_value ic : Natdynlink.dynheader) in | ||||
|     if header.magic <> Natdynlink.dyn_magic_number then | ||||
|       raise(Error(Natdynlink.Not_a_bytecode_file file)) | ||||
|     else begin | ||||
|       List.iter | ||||
|         (fun ui -> | ||||
|            print_infos | ||||
|              ui.name | ||||
|              ui.crc | ||||
|              ui.defines | ||||
|              ui.imports_cmi | ||||
|              ui.imports_cmx) | ||||
|         header.units | ||||
|     end | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user