File ocaml.ppc64.patch of Package ocaml

---
 asmcomp/power/proc.ml     |    2 
 asmrun/power-elf.S        |  225 ++++++++++++++++++++++++----------------------
 byterun/signals_machdep.h |   12 +-
 configure                 |    3 
 4 files changed, 129 insertions(+), 113 deletions(-)

--- a/asmcomp/power/proc.ml
+++ b/asmcomp/power/proc.ml
@@ -238,7 +238,7 @@ let assemble_file infile outfile =
   and outfile = Filename.quote outfile in
   match Config.system with
   | "elf" ->
-      Ccomp.command ("as -u -m ppc -o " ^ outfile ^ " " ^ infile)
+      Ccomp.command ("as -u -m " ^ Config.model ^ " -o " ^ outfile ^ " " ^ infile)
   | "rhapsody" ->
       Ccomp.command ("as -arch " ^ Config.model ^ " -o " ^ outfile ^ " " ^ infile)
   | "bsd" ->
--- a/asmrun/power-elf.S
+++ b/asmrun/power-elf.S
@@ -13,15 +13,27 @@
 
 /* $Id: power-elf.S,v 1.18 2004/01/03 12:51:19 doligez Exp $ */
 
+#ifdef __powerpc64__
+#define X(a,b) b
+#else
+#define X(a,b) a
+#endif
+
+#define WORD X(4,8)
+#define lg X(lwz,ld)
+#define lgu X(lwzu,ldu)
+#define stg X(stw,std)
+#define stgu X(stwu,stdu)
+#define gdata X(.long,.quad)
 #define Addrglobal(reg,glob) \
         addis   reg, 0, glob@ha; \
         addi    reg, reg, glob@l
 #define Loadglobal(reg,glob,tmp) \
         addis   tmp, 0, glob@ha; \
-        lwz     reg, glob@l(tmp)
+        lg     reg, glob@l(tmp)
 #define Storeglobal(reg,glob,tmp) \
         addis   tmp, 0, glob@ha; \
-        stw     reg, glob@l(tmp)
+        stg     reg, glob@l(tmp)
 
         .section ".text"
 
@@ -31,8 +43,8 @@
         .type   caml_call_gc, @function
 caml_call_gc:
     /* Set up stack frame */
-        stwu    1, -0x1A0(1)
-    /* 0x1A0 = 4*32 (int regs) + 8*32 (float regs) + 32 (space for C call) */
+        stgu    1, -0x1A0(1)
+    /* 0x1A0 = WORD*32 (int regs) + 8*32 (float regs) + 32 (space for C call) */
     /* Record return address into Caml code */
         mflr    0
         Storeglobal(0, caml_last_return_address, 11)
@@ -47,30 +59,30 @@ caml_call_gc:
     /* Save exception pointer (if e.g. a sighandler raises) */
         Storeglobal(29, caml_exception_pointer, 11)
     /* Save all registers used by the code generator */
-        addi    11, 1, 8*32 + 32 - 4
-        stwu    3, 4(11)
-        stwu    4, 4(11)
-        stwu    5, 4(11)
-        stwu    6, 4(11)
-        stwu    7, 4(11)
-        stwu    8, 4(11)
-        stwu    9, 4(11)
-        stwu    10, 4(11)
-        stwu    14, 4(11)
-        stwu    15, 4(11)
-        stwu    16, 4(11)
-        stwu    17, 4(11)
-        stwu    18, 4(11)
-        stwu    19, 4(11)
-        stwu    20, 4(11)
-        stwu    21, 4(11)
-        stwu    22, 4(11)
-        stwu    23, 4(11)
-        stwu    24, 4(11)
-        stwu    25, 4(11)
-        stwu    26, 4(11)
-        stwu    27, 4(11)
-        stwu    28, 4(11)
+        addi    11, 1, 8*32 + 32 - WORD
+        stgu    3, WORD(11)
+        stgu    4, WORD(11)
+        stgu    5, WORD(11)
+        stgu    6, WORD(11)
+        stgu    7, WORD(11)
+        stgu    8, WORD(11)
+        stgu    9, WORD(11)
+        stgu    10, WORD(11)
+        stgu    14, WORD(11)
+        stgu    15, WORD(11)
+        stgu    16, WORD(11)
+        stgu    17, WORD(11)
+        stgu    18, WORD(11)
+        stgu    19, WORD(11)
+        stgu    20, WORD(11)
+        stgu    21, WORD(11)
+        stgu    22, WORD(11)
+        stgu    23, WORD(11)
+        stgu    24, WORD(11)
+        stgu    25, WORD(11)
+        stgu    26, WORD(11)
+        stgu    27, WORD(11)
+        stgu    28, WORD(11)
         addi    11, 1, 32 - 8
         stfdu   1, 8(11)
         stfdu   2, 8(11)
@@ -109,30 +121,30 @@ caml_call_gc:
         Loadglobal(31, caml_young_ptr, 11)
         Loadglobal(30, caml_young_limit, 11)
     /* Restore all regs used by the code generator */
-        addi    11, 1, 8*32 + 32 - 4
-        lwzu    3, 4(11)
-        lwzu    4, 4(11)
-        lwzu    5, 4(11)
-        lwzu    6, 4(11)
-        lwzu    7, 4(11)
-        lwzu    8, 4(11)
-        lwzu    9, 4(11)
-        lwzu    10, 4(11)
-        lwzu    14, 4(11)
-        lwzu    15, 4(11)
-        lwzu    16, 4(11)
-        lwzu    17, 4(11)
-        lwzu    18, 4(11)
-        lwzu    19, 4(11)
-        lwzu    20, 4(11)
-        lwzu    21, 4(11)
-        lwzu    22, 4(11)
-        lwzu    23, 4(11)
-        lwzu    24, 4(11)
-        lwzu    25, 4(11)
-        lwzu    26, 4(11)
-        lwzu    27, 4(11)
-        lwzu    28, 4(11)
+        addi    11, 1, 8*32 + 32 - WORD
+        lgu    3, WORD(11)
+        lgu    4, WORD(11)
+        lgu    5, WORD(11)
+        lgu    6, WORD(11)
+        lgu    7, WORD(11)
+        lgu    8, WORD(11)
+        lgu    9, WORD(11)
+        lgu    10, WORD(11)
+        lgu    14, WORD(11)
+        lgu    15, WORD(11)
+        lgu    16, WORD(11)
+        lgu    17, WORD(11)
+        lgu    18, WORD(11)
+        lgu    19, WORD(11)
+        lgu    20, WORD(11)
+        lgu    21, WORD(11)
+        lgu    22, WORD(11)
+        lgu    23, WORD(11)
+        lgu    24, WORD(11)
+        lgu    25, WORD(11)
+        lgu    26, WORD(11)
+        lgu    27, WORD(11)
+        lgu    28, WORD(11)
         addi    11, 1, 32 - 8
         lfdu    1, 8(11)
         lfdu    2, 8(11)
@@ -185,6 +197,9 @@ caml_c_call:
     /* Save return address */
         mflr    25
     /* Get ready to call C function (address in 11) */
+#ifdef __powerpc64__
+	ld	11,4(11)
+#endif
         mtlr    11
     /* Record lowest stack address and return address */
         Storeglobal(1, caml_bottom_of_stack, 12)
@@ -218,8 +233,8 @@ caml_raise_exception:
         li      0, 0
         Storeglobal(0, caml_last_return_address, 11)
     /* Pop trap frame */
-        lwz     0, 0(1)
-        lwz     29, 4(1)
+        lg     0, 0(1)
+        lg     29, WORD(1)
         mtlr    0
         addi    1, 1, 16
     /* Branch to handler */
@@ -235,32 +250,32 @@ caml_start_program:
 /* Code shared between caml_start_program and caml_callback */
 .L102:
     /* Allocate and link stack frame */
-        stwu    1, -256(1)
+        stgu    1, -256(1)
     /* Save return address */
         mflr    0
-        stw     0, 256+4(1)
+        stg     0, 256+WORD(1)
     /* Save all callee-save registers */
     /* GPR 14 at sp+16 ... GPR 31 at sp+84
        FPR 14 at sp+92 ... FPR 31 at sp+228 */
-        addi    11, 1, 16-4
-        stwu    14, 4(11)
-        stwu    15, 4(11)
-        stwu    16, 4(11)
-        stwu    17, 4(11)
-        stwu    18, 4(11)
-        stwu    19, 4(11)
-        stwu    20, 4(11)
-        stwu    21, 4(11)
-        stwu    22, 4(11)
-        stwu    23, 4(11)
-        stwu    24, 4(11)
-        stwu    25, 4(11)
-        stwu    26, 4(11)
-        stwu    27, 4(11)
-        stwu    28, 4(11)
-        stwu    29, 4(11)
-        stwu    30, 4(11)
-        stwu    31, 4(11)
+        addi    11, 1, 16-WORD
+        stgu    14, WORD(11)
+        stgu    15, WORD(11)
+        stgu    16, WORD(11)
+        stgu    17, WORD(11)
+        stgu    18, WORD(11)
+        stgu    19, WORD(11)
+        stgu    20, WORD(11)
+        stgu    21, WORD(11)
+        stgu    22, WORD(11)
+        stgu    23, WORD(11)
+        stgu    24, WORD(11)
+        stgu    25, WORD(11)
+        stgu    26, WORD(11)
+        stgu    27, WORD(11)
+        stgu    28, WORD(11)
+        stgu    29, WORD(11)
+        stgu    30, WORD(11)
+        stgu    31, WORD(11)
         stfdu   14, 8(11)
         stfdu   15, 8(11)
         stfdu   16, 8(11)
@@ -284,18 +299,18 @@ caml_start_program:
         Loadglobal(9, caml_bottom_of_stack, 11)
         Loadglobal(10, caml_last_return_address, 11)
         Loadglobal(11, caml_gc_regs, 11)
-        stw     9, 0(1)
-        stw     10, 4(1)
-        stw     11, 8(1)
+        stg     9, 0(1)
+        stg     10, WORD(1)
+        stg     11, 2*WORD(1)
     /* Build an exception handler to catch exceptions escaping out of Caml */
         bl      .L103
         b       .L104
 .L103:
         addi    1, 1, -16
         mflr    0
-        stw     0, 0(1)
+        stg     0, 0(1)
         Loadglobal(11, caml_exception_pointer, 11)
-        stw     11, 4(1)
+        stg     11, WORD(1)
         mr      29, 1
     /* Reload allocation pointers */
         Loadglobal(31, caml_young_ptr, 11) 
@@ -308,14 +323,14 @@ caml_start_program:
 .L105:
         blrl
     /* Pop the trap frame, restoring caml_exception_pointer */
-        lwz     9, 4(1)
+        lg     9, WORD(1)
         Storeglobal(9, caml_exception_pointer, 11)
         addi    1, 1, 16
     /* Pop the callback link, restoring the global variables */
 .L106:
-        lwz     9, 0(1)
-        lwz     10, 4(1)
-        lwz     11, 8(1)
+        lg     9, 0(1)
+        lg     10, WORD(1)
+        lg     11, 2*WORD(1)
         Storeglobal(9, caml_bottom_of_stack, 12) 
         Storeglobal(10, caml_last_return_address, 12) 
         Storeglobal(11, caml_gc_regs, 12) 
@@ -323,25 +338,25 @@ caml_start_program:
     /* Update allocation pointer */
         Storeglobal(31, caml_young_ptr, 11)
     /* Restore callee-save registers */
-        addi    11, 1, 16-4
-        lwzu    14, 4(11)
-        lwzu    15, 4(11)
-        lwzu    16, 4(11)
-        lwzu    17, 4(11)
-        lwzu    18, 4(11)
-        lwzu    19, 4(11)
-        lwzu    20, 4(11)
-        lwzu    21, 4(11)
-        lwzu    22, 4(11)
-        lwzu    23, 4(11)
-        lwzu    24, 4(11)
-        lwzu    25, 4(11)
-        lwzu    26, 4(11)
-        lwzu    27, 4(11)
-        lwzu    28, 4(11)
-        lwzu    29, 4(11)
-        lwzu    30, 4(11)
-        lwzu    31, 4(11)
+        addi    11, 1, 16-WORD
+        lgu    14, WORD(11)
+        lgu    15, WORD(11)
+        lgu    16, WORD(11)
+        lgu    17, WORD(11)
+        lgu    18, WORD(11)
+        lgu    19, WORD(11)
+        lgu    20, WORD(11)
+        lgu    21, WORD(11)
+        lgu    22, WORD(11)
+        lgu    23, WORD(11)
+        lgu    24, WORD(11)
+        lgu    25, WORD(11)
+        lgu    26, WORD(11)
+        lgu    27, WORD(11)
+        lgu    28, WORD(11)
+        lgu    29, WORD(11)
+        lgu    30, WORD(11)
+        lgu    31, WORD(11)
         lfdu    14, 8(11)
         lfdu    15, 8(11)
         lfdu    16, 8(11)
@@ -361,7 +376,7 @@ caml_start_program:
         lfdu    30, 8(11)
         lfdu    31, 8(11)
     /* Reload return address */
-        lwz     0, 256+4(1)
+        lg     0, 256+ 2*WORD(1)
         mtlr    0
     /* Return */
         addi    1, 1, 256
@@ -384,7 +399,7 @@ caml_callback_exn:
         mr      0, 3            /* Closure */
         mr      3, 4            /* Argument */
         mr      4, 0
-        lwz     12, 0(4)        /* Code pointer */
+        lg     12, 0(4)        /* Code pointer */
         b       .L102
 
         .globl  caml_callback2_exn
--- a/byterun/signals_machdep.h
+++ b/byterun/signals_machdep.h
@@ -32,21 +32,21 @@
       : "=r" (dst), "=m" (src) \
       : "m" (src))
 
-#elif defined(__GNUC__) && defined(__ppc__)
+#elif defined(__GNUC__) && defined(__ppc64__)
 
 #define Read_and_clear(dst,src) \
-  asm("0: lwarx %0, 0, %1\n\t" \
-      "stwcx. %2, 0, %1\n\t" \
+  asm("0: ldarx %0, 0, %1\n\t" \
+      "stdcx. %2, 0, %1\n\t" \
       "bne- 0b" \
       : "=&r" (dst) \
       : "r" (&(src)), "r" (0) \
       : "cr0", "memory")
 
-#elif defined(__GNUC__) && defined(__ppc64__)
+#elif defined(__GNUC__) && defined(__ppc__)
 
 #define Read_and_clear(dst,src) \
-  asm("0: ldarx %0, 0, %1\n\t" \
-      "stdcx. %2, 0, %1\n\t" \
+  asm("0: lwarx %0, 0, %1\n\t" \
+      "stwcx. %2, 0, %1\n\t" \
       "bne- 0b" \
       : "=&r" (dst) \
       : "r" (&(src)), "r" (0) \
--- a/configure
+++ b/configure
@@ -589,7 +589,8 @@ case "$host" in
   hppa2.0*-*-hpux*)             arch=hppa; system=hpux;;
   hppa*-*-linux*)               arch=hppa; system=linux;;
   hppa*-*-gnu*)                 arch=hppa; system=gnu;;
-  powerpc*-*-linux*)            arch=power; model=ppc; system=elf;;
+  powerpc*-*-linux*)            arch=power; system=elf
+                                if $arch64; then model=ppc64; else model=ppc; fi;;
   powerpc-*-netbsd*)            arch=power; model=ppc; system=elf;;
   powerpc-*-rhapsody*)          arch=power; model=ppc; system=rhapsody;;
   powerpc-*-darwin*)            arch=power; system=rhapsody
openSUSE Build Service is sponsored by