Compare commits

...

13 Commits
master ... f17

Author SHA1 Message Date
Richard W.M. Jones db59fcdbd4 Includes fix for minor heap corruption because of unaligned minor heap
register (RHBZ#826649).

Unset MAKEFLAGS before running build.
(cherry picked from commit f67fde615d)
2012-06-06 19:28:06 +01:00
Richard W.M. Jones c9d7ae5a3e ppc64: Fix position of stack arguments to external C functions
when there are more than 8 parameters.
(cherry picked from commit 958f1c157a)
2012-06-06 13:39:28 +01:00
Richard W.M. Jones 2eca650954 - Include patch to link dllthreads.so with -lpthread explicitly, to
fix problem with 'pthread_atfork' symbol missing (statically linked)
  on ppc64.
(cherry picked from commit 963a64f016)
2012-06-06 13:39:24 +01:00
Richard W.M. Jones 8d2df37f2e - Include svn rev 12548 to fix invalid generation of Thumb-2 branch
instruction TBH (upstream PR#5623, RHBZ#821153).
(cherry picked from commit 1296d4b409)
2012-06-03 23:05:51 +01:00
Richard W.M. Jones 1a41274fac git am </dev/null to avoid hang (thanks Adam Jackson).
(cherry picked from commit 64a0f51339)
2012-06-03 23:05:48 +01:00
Richard W.M. Jones 51bbdb1bf9 Clean up the spec file and bring it up to modern standards.
* Remove patch fuzz directive.
  * Remove buildroot directive.
  * Rearrange source unpacking.
  * Remove chmod of GNU config.* files, since git does it.
  * Don't need to remove buildroot in install section.
  * Remove clean section.

Note that I didn't bump the release because there's no need to rebuild
it this time.
(cherry picked from commit 9cefc9cb13)
2012-06-03 23:05:44 +01:00
Richard W.M. Jones a6bda98b36 - Modify the ppc64 patch to reduce the delta between power64 and
upstream power backends.  Note there is no functional change.
(cherry picked from commit f3cfaea67e)
2012-06-03 23:05:41 +01:00
Richard W.M. Jones bb4c15fe90 BR +git
(cherry picked from commit 66cff0bf14)
2012-06-03 23:05:37 +01:00
Richard W.M. Jones 18e1a006ef Move patches to external git repo.
http://git.fedorahosted.org/git/?p=fedora-ocaml.git
(cherry picked from commit a07112286b)
2012-06-03 23:05:30 +01:00
Karsten Hopp 59555be647 apply patch on ppc archs only
(cherry picked from commit 7b1e4c1b84)
2012-05-17 17:23:39 +01:00
Karsten Hopp 30ba5522e2 add the patch
(cherry picked from commit 8ca22fff4b)
2012-05-17 17:23:35 +01:00
Karsten Hopp 7c0349dc89 ppc64 got broken by the new ARM backend, add a minor patch
(cherry picked from commit 4acc11f96b)
2012-05-17 17:23:32 +01:00
Richard W.M. Jones 09d74aee7e New ARM backend by Benedikt Meurer, backported to OCaml 3.12.1.
This has several advantages, including enabling natdynlink on ARM.

Provide updated config.guess and config.sub so we can detect the ARM
ABI correctly.
(cherry picked from commit 814f517596)
2012-04-30 08:49:09 +01:00
14 changed files with 6214 additions and 345 deletions

View 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/8] 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.1

File diff suppressed because it is too large Load Diff

View 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/8] 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.1

View 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/8] 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

View File

@ -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/8] 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

View File

@ -1,7 +1,48 @@
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
@@ -0,0 +1,84 @@
From b25707437651811a22acaab5a9461eb4ab742f6e 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/8] 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.
Includes fix for position of stack arguments to external C functions
when there are more than 8 parameters (RHBZ#829187).
Includes fix for minor heap corruption because of unaligned minor heap
register (RHBZ#826649).
---
asmcomp/power64/arch.ml | 83 ++++
asmcomp/power64/emit.mlp | 989 +++++++++++++++++++++++++++++++++++++++++
asmcomp/power64/proc.ml | 241 ++++++++++
asmcomp/power64/reload.ml | 18 +
asmcomp/power64/scheduling.ml | 65 +++
asmcomp/power64/selection.ml | 103 +++++
asmrun/Makefile | 6 +
asmrun/power64-elf.S | 486 ++++++++++++++++++++
asmrun/stack.h | 9 +
configure | 5 +-
10 files changed, 2004 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..55dd593
--- /dev/null
+++ b/asmcomp/power64/arch.ml
@@ -0,0 +1,83 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
@ -14,7 +55,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/arch.ml ocaml-3.10.1.ppc64/asmcomp/power6
+(* *)
+(***********************************************************************)
+
+(* $Id: ocaml-3.11.0-ppc64.patch,v 1.1 2008/11/20 15:30:55 rjones Exp $ *)
+(* $Id: arch.ml 9547 2010-01-22 12:48:24Z doligez $ *)
+
+(* Specific operations for the PowerPC processor *)
+
@ -44,7 +85,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/arch.ml ocaml-3.10.1.ppc64/asmcomp/power6
+let big_endian = true
+
+let size_addr = 8
+let size_int = 8
+let size_int = size_addr
+let size_float = 8
+
+(* Operations on addressing modes *)
@ -85,10 +126,11 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/arch.ml ocaml-3.10.1.ppc64/asmcomp/power6
+ printreg arg.(0) printreg arg.(1) printreg arg.(2)
+ | 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..42f585d
--- /dev/null
+++ b/asmcomp/power64/emit.mlp
@@ -0,0 +1,989 @@
+(***********************************************************************)
+(* *)
@ -102,7 +144,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/emit.mlp ocaml-3.10.1.ppc64/asmcomp/power
+(* *)
+(***********************************************************************)
+
+(* $Id: ocaml-3.11.0-ppc64.patch,v 1.1 2008/11/20 15:30:55 rjones Exp $ *)
+(* $Id: emit.mlp 9547 2010-01-22 12:48:24Z doligez $ *)
+
+(* Emission of PowerPC assembly code *)
+
@ -699,7 +741,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/emit.mlp ocaml-3.10.1.ppc64/asmcomp/power
+ ` bge {emit_label lbl}\n`;
+ record_frame i.live;
+ ` bl {emit_label !call_gc_label}\n`; (* Must be 4 insns to restart *)
+ `{emit_label lbl}: addi {emit_reg i.res.(0)}, {emit_gpr 31}, 4\n`
+ `{emit_label lbl}: addi {emit_reg i.res.(0)}, {emit_gpr 31}, {emit_int size_addr}\n`
+ | Lop(Iintop Isub) -> (* subfc has swapped arguments *)
+ ` subfc {emit_reg i.res.(0)}, {emit_reg i.arg.(1)}, {emit_reg i.arg.(0)}\n`
+ | Lop(Iintop Imod) ->
@ -1079,10 +1121,12 @@ 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
@@ -0,0 +1,245 @@
diff --git a/asmcomp/power64/proc.ml b/asmcomp/power64/proc.ml
new file mode 100644
index 0000000..119ad93
--- /dev/null
+++ b/asmcomp/power64/proc.ml
@@ -0,0 +1,241 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
@ -1095,7 +1139,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power6
+(* *)
+(***********************************************************************)
+
+(* $Id: ocaml-3.11.0-ppc64.patch,v 1.1 2008/11/20 15:30:55 rjones Exp $ *)
+(* $Id: proc.ml 9547 2010-01-22 12:48:24Z doligez $ *)
+
+(* Description of the Power PC *)
+
@ -1203,7 +1247,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power6
+ end else begin
+ loc.(i) <- stack_slot (make_stack !ofs) ty;
+ end;
+ ofs := !ofs + 8
+ ofs := !ofs + size_int
+ | Float ->
+ if !float <= last_float then begin
+ loc.(i) <- phys_reg !float;
@ -1211,7 +1255,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power6
+ end else begin
+ loc.(i) <- stack_slot (make_stack !ofs) Float;
+ end;
+ ofs := !ofs + 8
+ ofs := !ofs + size_float
+ done;
+ (loc, Misc.align !ofs 16)
+ (* Keep stack 16-aligned. *)
@ -1247,7 +1291,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power6
+ let loc = Array.create (Array.length arg) Reg.dummy in
+ let int = ref first_int in
+ let float = ref first_float in
+ let ofs = ref 112 in
+ let ofs = ref (14 * size_addr) in
+ for i = 0 to Array.length arg - 1 do
+ match arg.(i).typ with
+ Int | Addr as ty ->
@ -1273,7 +1317,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power6
+let loc_external_arguments =
+ match Config.system with
+ | "rhapsody" -> poweropen_external_conventions 0 7 100 112
+ | "elf" | "bsd" -> calling_conventions 0 7 100 107 outgoing 8
+ | "elf" | "bsd" -> calling_conventions 0 7 100 107 outgoing 48
+ | _ -> assert false
+
+let extcall_use_push = false
@ -1319,18 +1363,16 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/proc.ml ocaml-3.10.1.ppc64/asmcomp/power6
+(* Calling the assembler *)
+
+let assemble_file infile outfile =
+ let infile = Filename.quote infile
+ and outfile = Filename.quote outfile in
+ match Config.system with
+ | "elf" ->
+ Ccomp.command ("as -u -m ppc64 -o " ^ outfile ^ " " ^ infile)
+ | _ -> assert false
+ Ccomp.command (Config.asm ^ " -o " ^
+ Filename.quote outfile ^ " " ^ Filename.quote infile)
+
+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..abcac6c
--- /dev/null
+++ b/asmcomp/power64/reload.ml
@@ -0,0 +1,18 @@
+(***********************************************************************)
+(* *)
@ -1344,16 +1386,18 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/reload.ml ocaml-3.10.1.ppc64/asmcomp/powe
+(* *)
+(***********************************************************************)
+
+(* $Id: ocaml-3.11.0-ppc64.patch,v 1.1 2008/11/20 15:30:55 rjones Exp $ *)
+(* $Id: reload.ml 2553 1999-11-17 18:59:06Z xleroy $ *)
+
+(* Reloading for the PowerPC *)
+
+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
@@ -0,0 +1,66 @@
diff --git a/asmcomp/power64/scheduling.ml b/asmcomp/power64/scheduling.ml
new file mode 100644
index 0000000..b7bba9b
--- /dev/null
+++ b/asmcomp/power64/scheduling.ml
@@ -0,0 +1,65 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
@ -1366,7 +1410,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/scheduling.ml ocaml-3.10.1.ppc64/asmcomp/
+(* *)
+(***********************************************************************)
+
+(* $Id: ocaml-3.11.0-ppc64.patch,v 1.1 2008/11/20 15:30:55 rjones Exp $ *)
+(* $Id: scheduling.ml 9547 2010-01-22 12:48:24Z doligez $ *)
+
+(* Instruction scheduling for the Power PC *)
+
@ -1419,10 +1463,11 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/scheduling.ml ocaml-3.10.1.ppc64/asmcomp/
+end
+
+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..7b8e2a4
--- /dev/null
+++ b/asmcomp/power64/selection.ml
@@ -0,0 +1,103 @@
+(***********************************************************************)
+(* *)
@ -1436,7 +1481,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/selection.ml ocaml-3.10.1.ppc64/asmcomp/p
+(* *)
+(***********************************************************************)
+
+(* $Id: ocaml-3.11.0-ppc64.patch,v 1.1 2008/11/20 15:30:55 rjones Exp $ *)
+(* $Id: selection.ml 10296 2010-04-22 12:51:06Z xleroy $ *)
+
+(* Instruction selection for the Power PC processor *)
+
@ -1489,7 +1534,7 @@ diff -uNr ocaml-3.10.1/asmcomp/power64/selection.ml ocaml-3.10.1.ppc64/asmcomp/p
+ then (Iindexed2, Ctuple[e1; e2])
+ else (Iindexed d, Cop(Cadda, [e1; e2]))
+
+method select_operation op args =
+method! select_operation op args =
+ match (op, args) with
+ (* Prevent the recognition of (x / cst) and (x % cst) when cst is not
+ a power of 2, which do not correspond to an instruction. *)
@ -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

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,28 @@
From 66eef2038cf9af06e5883be320e3bf7aec35d572 Mon Sep 17 00:00:00 2001
From: "Richard W.M. Jones" <rjones@redhat.com>
Date: Tue, 5 Jun 2012 22:49:17 +0100
Subject: [PATCH 8/8] Link dllthreads.so with -lpthread so that pthread_atfork
is included statically.
See:
https://lists.fedoraproject.org/pipermail/ppc/2012-June/001655.html
---
otherlibs/systhreads/Makefile | 2 +-
1 file changed, 1 insertion(+), 1 deletion(-)
diff --git a/otherlibs/systhreads/Makefile b/otherlibs/systhreads/Makefile
index 5ee2775..c75ab14 100644
--- a/otherlibs/systhreads/Makefile
+++ b/otherlibs/systhreads/Makefile
@@ -30,7 +30,7 @@ all: libthreads.a threads.cma
allopt: libthreadsnat.a threads.cmxa
libthreads.a: $(BYTECODE_C_OBJS)
- $(MKLIB) -o threads $(BYTECODE_C_OBJS)
+ $(MKLIB) -o threads $(BYTECODE_C_OBJS) -lpthread
st_stubs_b.o: st_stubs.c st_posix.h
$(BYTECC) -O -I../../byterun $(BYTECCCOMPOPTS) $(SHAREDCCCOMPOPTS) \
--
1.7.10.1

View File

@ -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

View File

@ -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

View File

@ -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"

View File

@ -1,8 +1,6 @@
%global _default_patch_fuzz 2
Name: ocaml
Version: 3.12.1
Release: 2%{?dist}
Release: 12%{?dist}
Summary: Objective Caml compiler and programming environment
@ -16,21 +14,27 @@ 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
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
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
Patch0008: 0008-Link-dllthreads.so-with-lpthread-so-that-pthread_atf.patch
# Depend on previous version of OCaml so that ocamlobjinfo
# can run.
@ -56,10 +60,15 @@ BuildRequires: libXt-devel
BuildRequires: mesa-libGL-devel
BuildRequires: mesa-libGLU-devel
BuildRequires: chrpath
# git is required for patch management.
BuildRequires: git
Requires: gcc
Requires: ncurses-devel
Requires: gdbm-devel
Requires: rpm-build >= 4.8.0
Provides: ocaml(compiler) = %{version}
# We can compile OCaml on just about anything, but the native code
@ -72,7 +81,7 @@ ExclusiveArch: alpha %{arm} %{ix86} ia64 x86_64 ppc sparc sparcv9 ppc64
%global native_compiler 0
%endif
%ifarch %{ix86} ppc64 sparc sparcv9 x86_64
%ifarch %{arm} %{ix86} ppc64 sparc sparcv9 x86_64
%global natdynlink 1
%else
%global natdynlink 0
@ -219,18 +228,22 @@ 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
%endif
cp %{SOURCE2} refman.pdf
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} </dev/null
%build
CFLAGS="$RPM_OPT_FLAGS" ./configure \
# make -jN (N > 1) breaks the build. Therefore we cannot use
# %{?_smp_mflags} nor MAKEFLAGS.
unset MAKEFLAGS
CFLAGS="$RPM_OPT_FLAGS" \
./configure \
-bindir %{_bindir} \
-libdir %{_libdir}/ocaml \
-x11lib %{_libdir} \
@ -240,12 +253,10 @@ make world
%if %{native_compiler}
make opt opt.opt
%endif
# %{?_smp_mflags} breaks the build
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 .
@ -253,7 +264,6 @@ boot/ocamlrun ./ocamlc $includes dynlinkaux.cmo ocamlbyteinfo.ml -o ocamlbyteinf
%install
rm -rf $RPM_BUILD_ROOT
make install \
BINDIR=$RPM_BUILD_ROOT%{_bindir} \
LIBDIR=$RPM_BUILD_ROOT%{_libdir}/ocaml \
@ -284,10 +294,6 @@ install -m 0755 ocamlbyteinfo $RPM_BUILD_ROOT%{_bindir}
#install -m 0755 ocamlplugininfo $RPM_BUILD_ROOT%{_bindir}
%clean
rm -rf $RPM_BUILD_ROOT
%post docs
/sbin/install-info \
--entry="* ocaml: (ocaml). The Objective Caml compiler and programming environment" \
@ -492,6 +498,50 @@ fi
%changelog
* Wed Jun 6 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-12
- ppc64: Include fix for minor heap corruption because of unaligned
minor heap register (RHBZ#826649).
- Unset MAKEFLAGS before running build.
* Wed Jun 6 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-11
- ppc64: Fix position of stack arguments to external C functions
when there are more than 8 parameters.
* Tue Jun 5 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-10
- Include patch to link dllthreads.so with -lpthread explicitly, to
fix problem with 'pthread_atfork' symbol missing (statically linked)
on ppc64.
* Sun Jun 3 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-9
- Include svn rev 12548 to fix invalid generation of Thumb-2 branch
instruction TBH (upstream PR#5623, RHBZ#821153).
* Wed May 29 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-8
- Modify the ppc64 patch to reduce the delta between power64 and
upstream power backends.
- Clean up the spec file and bring it up to modern standards.
* Remove patch fuzz directive.
* Remove buildroot directive.
* Rearrange source unpacking.
* Remove chmod of GNU config.* files, since git does it.
* Don't need to remove buildroot in install section.
* Remove clean section.
* git am </dev/null to avoid hang (thanks Adam Jackson).
- Note there is no functional change in the above.
* Tue May 29 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-6
- 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
- New ARM backend by Benedikt Meurer, backported to OCaml 3.12.1.
This has several advantages, including enabling natdynlink on ARM.
- Provide updated config.guess and config.sub (from OCaml upstream tree).
* Thu Jan 12 2012 Richard W.M. Jones <rjones@redhat.com> 3.12.1-2
- add back ocaml-ppc64.patch for ppc secondary arch, drop .cmxs files
from file list on ppc (cherry picked from F16 - this should have

View File

@ -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))

View File

@ -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