summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2004-06-19 16:17:31 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2004-06-19 16:17:31 +0000
commit63b506d2cda0959f9811f0831580d8623c2511bc (patch)
treea0984e24e950feb5cc52c83ce112865268dbd855
parent9de985cc704443aad590e9950833d8b90edf8dfc (diff)
Suppression portage ocamlopt pour Power/AIX
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6423 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--README5
-rw-r--r--asmcomp/power/arch.ml19
-rw-r--r--asmcomp/power/emit.mlp287
-rw-r--r--asmcomp/power/proc.ml5
-rw-r--r--asmcomp/power/scheduling.ml4
-rw-r--r--asmcomp/power/selection.ml6
-rw-r--r--asmrun/signals.c38
-rw-r--r--config/Makefile-templ15
-rwxr-xr-xconfigure8
9 files changed, 70 insertions, 317 deletions
diff --git a/README b/README
index 400812aa5..5070eee75 100644
--- a/README
+++ b/README
@@ -21,15 +21,14 @@ native-code compiler currently runs on the following platforms:
Intel/AMD Pentium processors: PCs under Linux, FreeBSD, NetBSD,
OpenBSD, Windows, NextStep, Solaris 2, BeOS.
- PowerPC processors: PowerMacintosh under MacOS X and LinuxPPC,
- IBM RS6000 and PowerPC workstations under AIX 4.3
+ PowerPC processors: PowerMacintosh under MacOS X and LinuxPPC.
AMD64 (Opteron) processors: PCs under Linux.
Alpha processors: Digital/Compaq/HP Alpha machines under
Digital Unix/Compaq Tru64, Linux, NetBSD and OpenBSD.
Sparc processors: Sun Sparc machines under Solaris 2, NetBSD, Linux
Mips processors: SGI workstations and mainframes under IRIX 6
Intel IA64 processors: HP stations under Linux
- HP PA-RISC processors: HP 9000/700 under HPUX 10
+ HP PA-RISC processors: HP 9000/700 under HPUX 10 and Linux
Strong ARM processors: Corel Netwinder under Linux
Other operating systems for the processors above have not been tested,
diff --git a/asmcomp/power/arch.ml b/asmcomp/power/arch.ml
index 6b9bf5d9d..ace7bebd0 100644
--- a/asmcomp/power/arch.ml
+++ b/asmcomp/power/arch.ml
@@ -51,7 +51,7 @@ let offset_addressing addr delta =
match addr with
Ibased(s, n) -> Ibased(s, n + delta)
| Iindexed n -> Iindexed(n + delta)
- | Iindexed2 -> Misc.fatal_error "Arch_power.offset_addressing"
+ | Iindexed2 -> assert false
let num_args_addressing = function
Ibased(s, n) -> 0
@@ -82,20 +82,3 @@ let print_specific_operation printreg op ppf arg =
| Ialloc_far n ->
fprintf ppf "alloc_far %d" n
-(* Distinguish between the PowerPC and the Power/RS6000 submodels *)
-
-let powerpc =
- match Config.model with
- | "ppc" -> true
- | "rs6000" -> false
- | _ -> Misc.fatal_error "wrong $(MODEL)"
-
-(* Distinguish between the PowerOpen (AIX, MacOS) TOC-based,
- relative-addressing model and the SVR4 (Solaris, MkLinux, Rhapsody)
- absolute-addressing model. *)
-
-let toc =
- match Config.system with
- | "aix" -> true
- | "elf" | "rhapsody" | "bsd" -> false
- | _ -> Misc.fatal_error "wrong $(SYSTEM)"
diff --git a/asmcomp/power/emit.mlp b/asmcomp/power/emit.mlp
index 85a8b7a6f..7a04885cb 100644
--- a/asmcomp/power/emit.mlp
+++ b/asmcomp/power/emit.mlp
@@ -26,27 +26,12 @@ open Mach
open Linearize
open Emitaux
-(* Layout of the stack *)
-
-(* In the TOC-based model:
- The bottom 32 bytes of the stack are reserved at all times
- for a standard linkage area.
- In this area, the word at offset +20 is used by glue code and others to
- save the TOC register.
- The bottom two words are used as temporaries and for trap frames.
- The stack is kept 16-aligned.
- In the absolute-address model:
- No reserved space at the bottom of the stack.
- The stack is kept 16-aligned. *)
-
-let stack_linkage_area = if toc then 32 else 0
-let trap_frame_size = if toc then 32 else 16
+(* Layout of the stack. The stack is kept 16-aligned. *)
let stack_offset = ref 0
let frame_size () =
let size =
- stack_linkage_area + (* The bottom linkage area *)
!stack_offset + (* Trap frame, outgoing parameters *)
4 * num_stack_slots.(0) + 8 * num_stack_slots.(1) + (* Local variables *)
(if !contains_calls then 4 else 0) in (* The return address *)
@@ -56,8 +41,8 @@ let slot_offset loc cls =
match loc with
Local n ->
if cls = 0
- then stack_linkage_area + !stack_offset + num_stack_slots.(1) * 8 + n * 4
- else stack_linkage_area + !stack_offset + n * 8
+ then !stack_offset + num_stack_slots.(1) * 8 + n * 4
+ else !stack_offset + n * 8
| Incoming n -> frame_size() + n
| Outgoing n -> n
@@ -65,19 +50,14 @@ let slot_offset loc cls =
let emit_symbol =
match Config.system with
- "aix" | "elf" | "bsd" -> (fun s -> Emitaux.emit_symbol '.' s)
+ | "elf" | "bsd" -> (fun s -> Emitaux.emit_symbol '.' s)
| "rhapsody" -> (fun s -> emit_char '_'; Emitaux.emit_symbol '$' s)
| _ -> assert false
-let emit_codesymbol s =
- if toc then emit_char '.';
- emit_symbol s
-
(* Output a label *)
let label_prefix =
match Config.system with
- "aix" -> "L.."
| "elf" | "bsd" -> ".L"
| "rhapsody" -> "L"
| _ -> assert false
@@ -89,23 +69,20 @@ let emit_label lbl =
let data_space =
match Config.system with
- "aix" -> " .csect .data[RW]\n"
| "elf" | "bsd" -> " .section \".data\"\n"
- | "rhapsody" -> " .data\n"
+ | "rhapsody" -> " .data\n"
| _ -> assert false
let code_space =
match Config.system with
- "aix" -> " .csect .text[PR]\n"
| "elf" | "bsd" -> " .section \".text\"\n"
- | "rhapsody" -> " .text\n"
+ | "rhapsody" -> " .text\n"
| _ -> assert false
let rodata_space =
match Config.system with
- "aix" -> " .csect .data[RW]\n" (* ?? *)
| "elf" | "bsd" -> " .section \".rodata\"\n"
- | "rhapsody" -> " .const\n"
+ | "rhapsody" -> " .const\n"
| _ -> assert false
(* Output a pseudo-register *)
@@ -152,12 +129,11 @@ let is_immediate n =
let is_native_immediate n =
n <= Nativeint.of_int 32767 && n >= Nativeint.of_int (-32768)
-(* Output a "upper 16 bits" or "lower 16 bits" operator
- (for the absolute addressing mode) *)
+(* Output a "upper 16 bits" or "lower 16 bits" operator. *)
let emit_upper emit_fun arg =
match Config.system with
- "elf" | "bsd" ->
+ | "elf" | "bsd" ->
emit_fun arg; emit_string "@ha"
| "rhapsody" ->
emit_string "ha16("; emit_fun arg; emit_string ")"
@@ -165,7 +141,7 @@ let emit_upper emit_fun arg =
let emit_lower emit_fun arg =
match Config.system with
- "elf" | "bsd" ->
+ | "elf" | "bsd" ->
emit_fun arg; emit_string "@l"
| "rhapsody" ->
emit_string "lo16("; emit_fun arg; emit_string ")"
@@ -181,7 +157,6 @@ let emit_symbol_offset (s, d) =
let emit_load_store instr addressing_mode addr n arg =
match addressing_mode with
Ibased(s, d) ->
- (* Only relevant in the absolute model *)
` addis {emit_gpr 11}, 0, {emit_upper emit_symbol_offset (s,d)}\n`;
` {emit_string instr} {emit_reg arg}, {emit_lower emit_symbol_offset (s,d)}({emit_gpr 11})\n`
| Iindexed ofs ->
@@ -247,47 +222,12 @@ let emit_frame fd =
fd.fd_live_offset;
` .align 2\n`
-(* Record symbols and floating-point constants (for the TOC model).
- These will go in the toc section. *)
-
-let label_constant table constant =
- try
- Hashtbl.find table constant
- with Not_found ->
- let lbl = new_label() in
- Hashtbl.add table constant lbl;
- lbl
-
-let symbol_constants = (Hashtbl.create 17 : (string, int) Hashtbl.t)
-let float_constants = (Hashtbl.create 11 : (string, int) Hashtbl.t)
-
-let label_symbol s = label_constant symbol_constants s
-let label_float s = label_constant float_constants s
-
-let emit_symbol_constant symb lbl =
- `{emit_label lbl}: .tc {emit_symbol symb}[TC], {emit_symbol symb}\n`
-
-let emit_float_constant float lbl =
- `{emit_label lbl}: .tc FD_`;
- for i = 0 to 7 do
- emit_printf "%02x" (Char.code (String.unsafe_get float i))
- done;
- `[TC], 0x`;
- for i = 0 to 3 do
- emit_printf "%02x" (Char.code (String.unsafe_get float i))
- done;
- `, 0x`;
- for i = 4 to 7 do
- emit_printf "%02x" (Char.code (String.unsafe_get float i))
- done;
- `\n`
-
-(* Record floating-point literals (for the ELF model) *)
+(* Record floating-point literals *)
let float_literals = ref ([] : (string * int) list)
(* Record external C functions to be called in a position-independent way
- (for Rhapsody) *)
+ (for MacOSX) *)
let pic_externals = (Config.system = "rhapsody")
@@ -315,7 +255,7 @@ let name_for_int_comparison = function
let name_for_intop = function
Iadd -> "add"
| Imul -> "mullw"
- | Idiv -> if powerpc then "divw" else "divs"
+ | Idiv -> "divw"
| Iand -> "and"
| Ior -> "or"
| Ixor -> "xor"
@@ -378,17 +318,13 @@ let instr_size = function
Lend -> 0
| Lop(Imove | Ispill | Ireload) -> 1
| Lop(Iconst_int n) -> if is_native_immediate n then 1 else 2
- | Lop(Iconst_float s) -> if toc then 1 else 2
- | Lop(Iconst_symbol s) -> if toc then 1 else 2
- | Lop(Icall_ind) -> if toc then 6 else 2
- | Lop(Icall_imm s) ->
- if toc && not (StringSet.mem s !defined_functions) then 2 else 1
- | Lop(Itailcall_ind) -> if toc then 7 else 5
- | Lop(Itailcall_imm s) ->
- if s = !function_name then 1
- else if not toc || StringSet.mem s !defined_functions then 4
- else 8
- | Lop(Iextcall(s, true)) -> if toc then 2 else 3
+ | Lop(Iconst_float s) -> 2
+ | Lop(Iconst_symbol s) -> 2
+ | Lop(Icall_ind) -> 2
+ | Lop(Icall_imm s) -> 1
+ | Lop(Itailcall_ind) -> 5
+ | Lop(Itailcall_imm s) -> if s = !function_name then 1 else 4
+ | Lop(Iextcall(s, true)) -> 3
| Lop(Iextcall(s, false)) -> if pic_externals then 4 else 1
| Lop(Istackoffset n) -> 1
| Lop(Iload(chunk, addr)) ->
@@ -398,7 +334,7 @@ let instr_size = function
| Lop(Istore(chunk, addr)) -> load_store_size addr
| Lop(Ialloc n) -> 4
| Lop(Ispecific(Ialloc_far n)) -> 5
- | Lop(Iintop Imod) -> if powerpc then 3 else 2
+ | Lop(Iintop Imod) -> 3
| Lop(Iintop(Icomp cmp)) -> 4
| Lop(Iintop op) -> 1
| Lop(Iintop_imm(Idiv, n)) -> 2
@@ -420,9 +356,9 @@ let instr_size = function
+ (if lbl2 = None then 0 else 1)
| Lswitch jumptbl -> 8
| Lsetuptrap lbl -> 1
- | Lpushtrap -> if toc then 5 else 4
+ | Lpushtrap -> 4
| Lpoptrap -> 2
- | Lraise -> if toc then 7 else 6
+ | Lraise -> 6
let label_map code =
let map = Hashtbl.create 37 in
@@ -526,52 +462,23 @@ let rec emit_instr i dslot =
` ori {emit_reg i.res.(0)}, {emit_reg i.res.(0)}, {emit_int(nativelow n)}\n`
end
| Lop(Iconst_float s) ->
- if toc then begin
- let repr = (Obj.magic (float_of_string s) : string) in
- let lbl = label_float repr in
- ` lfd {emit_reg i.res.(0)}, {emit_label lbl}(2) # {emit_string s}\n`
- end else begin
- let lbl = new_label() in
- float_literals := (s, lbl) :: !float_literals;
- ` addis {emit_gpr 11}, 0, {emit_upper emit_label lbl}\n`;
- ` lfd {emit_reg i.res.(0)}, {emit_lower emit_label lbl}({emit_gpr 11})\n`
- end
+ let lbl = new_label() in
+ float_literals := (s, lbl) :: !float_literals;
+ ` addis {emit_gpr 11}, 0, {emit_upper emit_label lbl}\n`;
+ ` lfd {emit_reg i.res.(0)}, {emit_lower emit_label lbl}({emit_gpr 11})\n`
| Lop(Iconst_symbol s) ->
- if toc then begin
- let lbl = label_symbol s in
- ` lwz {emit_reg i.res.(0)}, {emit_label lbl}(2) # {emit_symbol s}\n`
- end else begin
- ` addis {emit_reg i.res.(0)}, 0, {emit_upper emit_symbol s}\n`;
- ` addi {emit_reg i.res.(0)}, {emit_reg i.res.(0)}, {emit_lower emit_symbol s}\n`
- end
+ ` addis {emit_reg i.res.(0)}, 0, {emit_upper emit_symbol s}\n`;
+ ` addi {emit_reg i.res.(0)}, {emit_reg i.res.(0)}, {emit_lower emit_symbol s}\n`
| Lop(Icall_ind) ->
- if toc then begin
- ` lwz 0, 0({emit_reg i.arg.(0)})\n`;
- ` stw 2, 20(1)\n`;
- ` mtctr 0\n`;
- ` lwz 2, 4({emit_reg i.arg.(0)})\n`;
- record_frame i.live;
- ` bctrl\n`;
- ` lwz 2, 20(1)\n`
- end else begin
- ` mtctr {emit_reg i.arg.(0)}\n`;
- record_frame i.live;
- ` bctrl\n`
- end
+ ` mtctr {emit_reg i.arg.(0)}\n`;
+ record_frame i.live;
+ ` bctrl\n`
| Lop(Icall_imm s) ->
record_frame i.live;
- ` bl {emit_codesymbol s}\n`;
- if toc && not (StringSet.mem s !defined_functions) then
- ` cror 31, 31, 31\n` (* nop *)
+ ` bl {emit_symbol s}\n`
| Lop(Itailcall_ind) ->
let n = frame_size() in
- if toc then begin
- ` lwz 0, 0({emit_reg i.arg.(0)})\n`;
- ` lwz 2, 4({emit_reg i.arg.(0)})\n`;
- ` mtctr 0\n`
- end else begin
- ` mtctr {emit_reg i.arg.(0)}\n`
- end;
+ ` mtctr {emit_reg i.arg.(0)}\n`;
if !contains_calls then begin
` lwz {emit_gpr 11}, {emit_int(n - 4)}({emit_gpr 1})\n`;
` addi {emit_gpr 1}, {emit_gpr 1}, {emit_int n}\n`;
@@ -584,7 +491,7 @@ let rec emit_instr i dslot =
| Lop(Itailcall_imm s) ->
if s = !function_name then
` b {emit_label !tailrec_entry_point}\n`
- else if not toc || StringSet.mem s !defined_functions then begin
+ else begin
let n = frame_size() in
if !contains_calls then begin
` lwz {emit_gpr 11}, {emit_int(n - 4)}({emit_gpr 1})\n`;
@@ -594,38 +501,11 @@ let rec emit_instr i dslot =
if n > 0 then
` addi {emit_gpr 1}, {emit_gpr 1}, {emit_int n}\n`
end;
- ` b {emit_codesymbol s}\n`
- end else begin
- (* Tailcalling a function that has a possibly different TOC
- is difficult, because the callee's TOC must be loaded in r2,
- but ours must not be stored in 20(r1), which would overwrite
- our caller's saved TOC. Hence we can't go through the
- standard glue code. Here, we just proceed as in tailcall_ind. *)
- let lbl = label_symbol s in
- let n = frame_size() in
- ` lwz 12, {emit_label lbl}(2) # {emit_symbol s}\n`;
- if !contains_calls then begin
- ` lwz 0, 0(12)\n`;
- ` lwz 2, 4(12)\n`;
- ` mtctr 0\n`;
- ` lwz 11, {emit_int(n - 4)}(1)\n`;
- ` addi 1, 1, {emit_int n}\n`;
- ` mtlr 11\n`
- end else begin
- ` lwz 0, 0(12)\n`;
- ` lwz 2, 4(12)\n`;
- ` mtctr 0\n`;
- if n > 0 then
- ` addi 1, 1, {emit_int n}\n`
- end;
- ` bctr\n`
+ ` b {emit_symbol s}\n`
end
| Lop(Iextcall(s, alloc)) ->
if alloc then begin
- if toc then begin
- let lbl = label_symbol s in
- ` lwz 11, {emit_label lbl}(2) # {emit_symbol s}\n`
- end else if pic_externals then begin
+ if pic_externals then begin
external_functions := StringSet.add s !external_functions;
` addis {emit_gpr 11}, 0, ha16(L{emit_symbol s}$non_lazy_ptr)\n`;
` lwz {emit_gpr 11}, lo16(L{emit_symbol s}$non_lazy_ptr)({emit_gpr 11})\n`
@@ -634,7 +514,7 @@ let rec emit_instr i dslot =
` addi {emit_gpr 11}, {emit_gpr 11}, {emit_lower emit_symbol s}\n`
end;
record_frame i.live;
- ` bl {emit_codesymbol "caml_c_call"}\n`
+ ` bl {emit_symbol "caml_c_call"}\n`
end else begin
if pic_externals then begin
external_functions := StringSet.add s !external_functions;
@@ -643,10 +523,8 @@ let rec emit_instr i dslot =
` mtctr {emit_gpr 11}\n`;
` bctrl\n`
end else
- ` bl {emit_codesymbol s}\n`
- end;
- if toc then
- ` cror 31, 31, 31\n` (* nop *)
+ ` bl {emit_symbol s}\n`
+ end
| Lop(Istackoffset n) ->
` addi {emit_gpr 1}, {emit_gpr 1}, {emit_int (-n)}\n`;
stack_offset := !stack_offset + n
@@ -688,18 +566,12 @@ let rec emit_instr i dslot =
record_frame i.live;
` bl {emit_label !call_gc_label}\n`;
`{emit_label lbl}: addi {emit_reg i.res.(0)}, {emit_gpr 31}, 4\n`
- | Lop(Iintop Isub) -> (* subf has swapped arguments *)
- (* Use subfc instead of subf for RS6000 compatibility. *)
+ | 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) ->
- if powerpc then begin
- ` divw {emit_gpr 0}, {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}\n`;
- ` mullw {emit_gpr 0}, {emit_gpr 0}, {emit_reg i.arg.(1)}\n`;
- ` subfc {emit_reg i.res.(0)}, {emit_gpr 0}, {emit_reg i.arg.(0)}\n`
- end else begin
- ` divs {emit_gpr 0}, {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}\n`;
- ` mfmq {emit_reg i.res.(0)}\n`
- end
+ ` divw {emit_gpr 0}, {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}\n`;
+ ` mullw {emit_gpr 0}, {emit_gpr 0}, {emit_reg i.arg.(1)}\n`;
+ ` subfc {emit_reg i.res.(0)}, {emit_gpr 0}, {emit_reg i.arg.(0)}\n`
| Lop(Iintop(Icomp cmp)) ->
begin match cmp with
Isigned c ->
@@ -747,17 +619,11 @@ let rec emit_instr i dslot =
let instr = name_for_floatop2 op in
` {emit_string instr} {emit_reg i.res.(0)}, {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}\n`
| Lop(Ifloatofint) ->
- if toc then begin
- let lbl = label_float "\067\048\000\000\128\000\000\000" in
- (* That string above represents 0x4330000080000000 *)
- ` lfd 0, {emit_label lbl}(2)\n`
- end else begin
- let lbl = new_label() in
- float_literals := ("4.503601774854144e15", lbl) :: !float_literals;
- (* That float above also represents 0x4330000080000000 *)
- ` addis {emit_gpr 11}, 0, {emit_upper emit_label lbl}\n`;
- ` lfd {emit_fpr 0}, {emit_lower emit_label lbl}({emit_gpr 11})\n`
- end;
+ let lbl = new_label() in
+ float_literals := ("4.503601774854144e15", lbl) :: !float_literals;
+ (* That float above represents 0x4330000080000000 *)
+ ` addis {emit_gpr 11}, 0, {emit_upper emit_label lbl}\n`;
+ ` lfd {emit_fpr 0}, {emit_lower emit_label lbl}({emit_gpr 11})\n`;
` lis {emit_gpr 0}, 0x4330\n`;
` stwu {emit_gpr 0}, -8({emit_gpr 1})\n`;
` xoris {emit_gpr 0}, {emit_reg i.arg.(0)}, 0x8000\n`;
@@ -849,12 +715,8 @@ let rec emit_instr i dslot =
end
| Lswitch jumptbl ->
if !lbl_jumptbl = 0 then lbl_jumptbl := new_label();
- if toc then begin
- ` lwz 11, {emit_label !lbl_jumptbl}(2)\n`
- end else begin
- ` addis {emit_gpr 11}, 0, {emit_upper emit_label !lbl_jumptbl}\n`;
- ` addi {emit_gpr 11}, {emit_gpr 11}, {emit_lower emit_label !lbl_jumptbl}\n`
- end;
+ ` addis {emit_gpr 11}, 0, {emit_upper emit_label !lbl_jumptbl}\n`;
+ ` addi {emit_gpr 11}, {emit_gpr 11}, {emit_lower emit_label !lbl_jumptbl}\n`;
` addi {emit_gpr 0}, {emit_reg i.arg.(0)}, {emit_int !num_jumptbl_entries}\n`;
` slwi {emit_gpr 0}, {emit_gpr 0}, 2\n`;
` lwzx {emit_gpr 0}, {emit_gpr 11}, {emit_gpr 0}\n`;
@@ -868,25 +730,21 @@ let rec emit_instr i dslot =
| Lsetuptrap lbl ->
` bl {emit_label lbl}\n`
| Lpushtrap ->
- stack_offset := !stack_offset + trap_frame_size;
+ stack_offset := !stack_offset + 16;
` mflr {emit_gpr 0}\n`;
- ` stwu {emit_gpr 0}, -{emit_int trap_frame_size}({emit_gpr 1})\n`;
+ ` stwu {emit_gpr 0}, -16({emit_gpr 1})\n`;
` stw {emit_gpr 29}, 4({emit_gpr 1})\n`;
- if toc then
- ` stw {emit_gpr 2}, 20({emit_gpr 1})\n`;
` mr {emit_gpr 29}, {emit_gpr 1}\n`
| Lpoptrap ->
` lwz {emit_gpr 29}, 4({emit_gpr 1})\n`;
- ` addi {emit_gpr 1}, {emit_gpr 1}, {emit_int trap_frame_size}\n`;
- stack_offset := !stack_offset - trap_frame_size
+ ` addi {emit_gpr 1}, {emit_gpr 1}, 16\n`;
+ stack_offset := !stack_offset - 16
| Lraise ->
` lwz {emit_gpr 0}, 0({emit_gpr 29})\n`;
` mr {emit_gpr 1}, {emit_gpr 29}\n`;
` mtlr {emit_gpr 0}\n`;
` lwz {emit_gpr 29}, 4({emit_gpr 1})\n`;
- if toc then
- ` lwz {emit_gpr 2}, 20({emit_gpr 1})\n`;
- ` addi {emit_gpr 1}, {emit_gpr 1}, {emit_int trap_frame_size}\n`;
+ ` addi {emit_gpr 1}, {emit_gpr 1}, 16\n`;
` blr\n`
and emit_delay = function
@@ -946,18 +804,13 @@ let fundecl fundecl =
float_literals := [];
` .globl {emit_symbol fundecl.fun_name}\n`;
begin match Config.system with
- "aix" ->
- ` .globl .{emit_symbol fundecl.fun_name}\n`;
- ` .csect {emit_symbol fundecl.fun_name}[DS]\n`;
- `{emit_symbol fundecl.fun_name}:\n`;
- ` .long .{emit_symbol fundecl.fun_name}, TOC[tc0], 0\n`
| "elf" | "bsd" ->
` .type {emit_symbol fundecl.fun_name}, @function\n`
| _ -> ()
end;
emit_string code_space;
` .align 2\n`;
- `{emit_codesymbol fundecl.fun_name}:\n`;
+ `{emit_symbol fundecl.fun_name}:\n`;
let n = frame_size() in
if !contains_calls then begin
` mflr {emit_gpr 0}\n`;
@@ -973,14 +826,7 @@ let fundecl fundecl =
(* Emit the glue code to call the GC *)
if !call_gc_label > 0 then begin
`{emit_label !call_gc_label}:\n`;
- if toc then begin
- ` mflr 0\n`; (* Save return address in r0 *)
- ` bl .caml_call_gc\n`;
- ` cror 31, 31, 31\n`; (* nop *)
- ` blr\n` (* Will re-execute the allocation *)
- end else begin
- ` b {emit_symbol "caml_call_gc"}\n`
- end
+ ` b {emit_symbol "caml_call_gc"}\n`
end;
(* Emit the floating-point literals *)
if !float_literals <> [] then begin
@@ -1056,26 +902,13 @@ let begin_assembly() =
let end_assembly() =
(* Emit the jump table *)
if !num_jumptbl_entries > 0 then begin
- let lbl_tbl =
- if toc then begin
- let lbl_tbl = new_label() in
- ` .toc\n`;
- `{emit_label !lbl_jumptbl}: .tc {emit_label lbl_tbl}[TC], {emit_label lbl_tbl}\n`;
- lbl_tbl
- end else !lbl_jumptbl in
emit_string code_space;
- `{emit_label lbl_tbl}:\n`;
+ `{emit_label !lbl_jumptbl}:\n`;
List.iter
- (fun lbl -> ` .long {emit_label lbl} - {emit_label lbl_tbl}\n`)
+ (fun lbl -> ` .long {emit_label lbl} - {emit_label !lbl_jumptbl}\n`)
(List.rev !jumptbl_entries);
jumptbl_entries := []
end;
- if toc then begin
- (* Emit the table of constants *)
- ` .toc\n`;
- Hashtbl.iter emit_symbol_constant symbol_constants;
- Hashtbl.iter emit_float_constant float_constants
- end;
if pic_externals then
(* Emit the pointers to external functions *)
StringSet.iter emit_external !external_functions;
diff --git a/asmcomp/power/proc.ml b/asmcomp/power/proc.ml
index f0dabff13..4c1d96dfd 100644
--- a/asmcomp/power/proc.ml
+++ b/asmcomp/power/proc.ml
@@ -189,7 +189,7 @@ let poweropen_external_conventions first_int last_int
let loc_external_arguments =
match Config.system with
- "aix" | "rhapsody" -> poweropen_external_conventions 0 7 100 112
+ | "rhapsody" -> poweropen_external_conventions 0 7 100 112
| "elf" | "bsd" -> calling_conventions 0 7 100 107 outgoing 8
| _ -> assert false
@@ -239,9 +239,6 @@ let assemble_file infile outfile =
let infile = Filename.quote infile
and outfile = Filename.quote outfile in
match Config.system with
- "aix" ->
- let proc = if powerpc then "ppc" else "pwr" in
- Ccomp.command ("as -u -m " ^ proc ^ " -o " ^ outfile ^ " " ^ infile)
| "elf" ->
Ccomp.command ("as -u -m ppc -o " ^ outfile ^ " " ^ infile)
| "rhapsody" | "bsd" ->
diff --git a/asmcomp/power/scheduling.ml b/asmcomp/power/scheduling.ml
index 31e6f9b22..ef3a77b34 100644
--- a/asmcomp/power/scheduling.ml
+++ b/asmcomp/power/scheduling.ml
@@ -27,7 +27,7 @@ method oper_latency = function
Ireload -> 2
| Iload(_, _) -> 2
| Iconst_float _ -> 2 (* turned into a load *)
- | Iconst_symbol _ -> if toc then 2 (* turned into a load *) else 1
+ | Iconst_symbol _ -> 1
| Iintop Imul -> 9
| Iintop_imm(Imul, _) -> 5
| Iintop(Idiv | Imod) -> 36
@@ -44,7 +44,7 @@ method reload_retaddr_latency = 12
(* Issue cycles. Rough approximations. *)
method oper_issue_cycles = function
- Iconst_float _ | Iconst_symbol _ -> if toc then 1 else 2
+ Iconst_float _ | Iconst_symbol _ -> 2
| Iload(_, Ibased(_, _)) -> 2
| Istore(_, Ibased(_, _)) -> 2
| Ialloc _ -> 4
diff --git a/asmcomp/power/selection.ml b/asmcomp/power/selection.ml
index 37ac6cde1..f3880b0da 100644
--- a/asmcomp/power/selection.ml
+++ b/asmcomp/power/selection.ml
@@ -28,8 +28,7 @@ type addressing_expr =
| Aadd of expression * expression
let rec select_addr = function
- Cconst_symbol s when not toc ->
- (* don't recognize this mode in the TOC-based model *)
+ Cconst_symbol s ->
(Asymbol s, 0)
| Cop((Caddi | Cadda), [arg; Cconst_int m]) ->
let (a, n) = select_addr arg in (a, n + m)
@@ -81,9 +80,6 @@ method select_operation op args =
| (Cand, _) -> self#select_logical Iand args
| (Cor, _) -> self#select_logical Ior args
| (Cxor, _) -> self#select_logical Ixor args
- (* intoffloat goes through a library function on the RS6000 *)
- | (Cintoffloat, _) when not powerpc ->
- (Iextcall("itrunc", false), args)
(* Recognize mult-add and mult-sub instructions *)
| (Caddf, [Cop(Cmulf, [arg1; arg2]); arg3]) ->
(Ispecific Imultaddf, [arg1; arg2; arg3])
diff --git a/asmrun/signals.c b/asmrun/signals.c
index efc73ce7e..a6ce72ef7 100644
--- a/asmrun/signals.c
+++ b/asmrun/signals.c
@@ -109,18 +109,6 @@ extern sighandler caml_win32_signal(int sig, sighandler action);
#endif
#endif
-#if defined(TARGET_power) && defined(SYS_aix)
-#ifdef _AIXVERSION_430
-#define STRUCT_SIGCONTEXT struct __sigcontext
-#define CONTEXT_GPR(ctx, regno) \
- ((ctx)->__sc_jmpbuf.__jmp_context.__gpr[(regno)])
-#else
-#define STRUCT_SIGCONTEXT struct sigcontext
-#define CONTEXT_GPR(ctx, regno) \
- ((ctx)->sc_jmpbuf.jmp_context.gpr[(regno)])
-#endif
-#endif
-
volatile int caml_async_signal_mode = 0;
volatile int caml_pending_signal = 0;
volatile int caml_force_major_slice = 0;
@@ -226,8 +214,6 @@ void caml_leave_blocking_section(void)
#if defined(TARGET_alpha) || defined(TARGET_mips)
static void handle_signal(int sig, int code, struct sigcontext * context)
-#elif defined(TARGET_power) && defined(SYS_aix)
-static void handle_signal(int sig, int code, STRUCT_SIGCONTEXT * context)
#elif defined(TARGET_power) && defined(SYS_elf)
static void handle_signal(int sig, struct sigcontext * context)
#elif defined(TARGET_power) && defined(SYS_rhapsody)
@@ -270,12 +256,6 @@ static void handle_signal(int sig)
context->sc_regs[23] = (int) caml_young_limit;
}
#endif
-#if defined(TARGET_power) && defined(SYS_aix)
- if (caml_last_return_address == 0) {
- /* Cached in register 30 */
- CONTEXT_GPR(context, 30) = (ulong_t) caml_young_limit;
- }
-#endif
#if defined(TARGET_power) && defined(SYS_elf)
if (caml_last_return_address == 0) {
/* Cached in register 30 */
@@ -504,22 +484,6 @@ static void trap_handler(int sig)
}
#endif
-#if defined(TARGET_power) && defined(SYS_aix)
-static void trap_handler(int sig, int code, STRUCT_SIGCONTEXT * context)
-{
- /* Unblock SIGTRAP */
- sigset_t mask;
- sigemptyset(&mask);
- sigaddset(&mask, SIGTRAP);
- sigprocmask(SIG_UNBLOCK, &mask, NULL);
- /* Recover [caml_young_ptr] and [caml_exception_pointer]
- from registers 31 and 29 */
- caml_exception_pointer = (char *) CONTEXT_GPR(context, 29);
- caml_young_ptr = (char *) CONTEXT_GPR(context, 31);
- caml_array_bound_error();
-}
-#endif
-
#if defined(TARGET_power) && defined(SYS_elf)
static void trap_handler(int sig, struct sigcontext * context)
{
@@ -640,8 +604,6 @@ void caml_init_signals(void)
sigemptyset(&act.sa_mask);
#if defined (SYS_rhapsody)
act.sa_flags = SA_SIGINFO;
-#elif defined (SYS_aix)
- act.sa_flags = 0;
#else
act.sa_flags = SA_NODEFER;
#endif
diff --git a/config/Makefile-templ b/config/Makefile-templ
index 73180db01..a8b2ea01a 100644
--- a/config/Makefile-templ
+++ b/config/Makefile-templ
@@ -111,8 +111,8 @@ SHARPBANGSCRIPTS=true
### i386 Intel Pentium PCs under Linux, *BSD*, NextStep
### sparc Sun Sparcstation under SunOS 4.1 or Solaris 2
### mips SGI machines under IRIX
-### hppa HP 9000/700 under HPUX
-### power Mac OS X; IBM RS6000 and PowerPC workstations under AIX
+### hppa HP 9000/700 under HPUX and Linux
+### power Macintosh under Mac OS X and Linux
### ia64 Intel Itanium/IA64 under Linux
### arm ARM under Linux
###
@@ -133,18 +133,9 @@ SHARPBANGSCRIPTS=true
### behavior of the code generator to the particular flavor used.
### Currently needed only if ARCH=power; leave MODEL=default for
### other architectures.
-### If ARCH=power: choose between
-### MODEL=rs6000 The original IBM RS6000 workstations
-### (RIOS and RIOS2 processors)
-### MODEL=ppc The newer PowerPC processors
-### (Motorola/IBM PPC601, PPC603, PPC604, G3, G4, etc)
-### The Motorola PPC601 is compatible with both models, but the newer
-### PPCs will work only with MODEL=ppc, and the older IBM RS6000
-### workstations will work only with MODEL=rs6000.
-###
+### If ARCH=power: set MODEL=ppc
### For other architectures: leave MODEL=default
###
-#MODEL=rs6000
#MODEL=ppc
#MODEL=default
diff --git a/configure b/configure
index b69c2e409..3d184e02b 100755
--- a/configure
+++ b/configure
@@ -577,8 +577,6 @@ case "$host" in
hppa1.1-*-hpux*) arch=hppa; system=hpux;;
hppa2.0*-*-hpux*) arch=hppa; system=hpux;;
hppa*-*-linux*) arch=hppa; system=linux;;
- rs6000-*-aix*) arch=power; model=rs6000; system=aix;;
- powerpc-*-aix*) arch=power; model=ppc; system=aix;;
powerpc-*-linux*) arch=power; model=ppc; system=elf;;
powerpc-*-netbsd*) arch=power; model=ppc; system=bsd;;
powerpc-*-rhapsody*) arch=power; model=ppc; system=rhapsody;;
@@ -608,10 +606,6 @@ case "$arch,$nativecc,$system,$host_type" in
alpha,cc*,digital,*) nativecccompopts=-std1;;
mips,cc*,irix,*) nativecccompopts=-n32
nativecclinkopts="-n32 -Wl,-woff,84";;
- power,gcc*,aix,*aix4.3*)
- nativecccompopts="$gcc_warnings -D_XOPEN_SOURCE=500";;
- power,*,aix,*aix4.3*)
- nativecccompopts="-D_XOPEN_SOURCE=500";;
*,*,nextstep,*) nativecccompopts="$gcc_warnings -U__GNUC__ -posix"
nativecclinkopts="-posix";;
*,*,rhapsody,*darwin6*)
@@ -643,8 +637,6 @@ case "$arch,$model,$system" in
i386,*,solaris) aspp='/usr/ccs/bin/as'; asppflags='-P -DSYS_$(SYSTEM)';;
i386,*,*) aspp='gcc'; asppflags='-c -DSYS_$(SYSTEM)';;
hppa,*,*) aspp="$cc"; asppflags='-traditional -c -DSYS_$(SYSTEM)';;
- power,rs6000,aix) asflags='-u -m pwr -w'; asppflags="$asflags";;
- power,ppc,aix) asflags='-u -m ppc -w'; asppflags="$asflags";;
power,*,elf) aspp='gcc'; asppflags='-c';;
power,*,bsd) aspp='gcc'; asppflags='-c -DSYS_$(SYSTEM)';;
power,*,rhapsody) ;;