diff --git a/asmcomp/arm/emit.mlp b/asmcomp/arm/emit.mlp index 61908351f07e..c007c5fc1f29 100644 --- a/asmcomp/arm/emit.mlp +++ b/asmcomp/arm/emit.mlp @@ -359,7 +359,7 @@ let emit_instr i = ` {emit_string instr} {emit_reg r}, {emit_addressing addr i.arg 1}\n`; 1 | Lop(Ialloc n) -> - let nn = Nativeint.from n in + let nn = Nativeint.from n in if !fastcode_flag then begin if is_immediate nn then begin ` ldr r10, [alloc_limit, #0]\n`; diff --git a/asmcomp/arm/proc.ml b/asmcomp/arm/proc.ml index e89497c7bdce..24bda41a8143 100644 --- a/asmcomp/arm/proc.ml +++ b/asmcomp/arm/proc.ml @@ -43,7 +43,7 @@ let word_addressed = false let int_reg_name = [| "r0"; "r1"; "r2"; "r3"; "r4"; "r5"; "r6"; "r7"; "r10"; "r12" |] - + let float_reg_name = [| "f0"; "f1"; "f2"; "f3"; "f4"; "f5"; "f6"; "f7" |] @@ -167,7 +167,7 @@ let destroyed_at_c_call = (* r4-r9, f4-f7 preserved *) let destroyed_at_oper = function Iop(Icall_ind | Icall_imm _ | Iextcall(_, true)) -> all_phys_regs | Iop(Iextcall(_, false)) -> destroyed_at_c_call - | Iop(Ialloc(_)) -> [|phys_reg 8|] (* r10 destroyed *) + | Iop(Ialloc(_)) -> [|phys_reg 8|] (* r10 destroyed *) | _ -> [||] let destroyed_at_raise = all_phys_regs diff --git a/asmcomp/arm/selection.ml b/asmcomp/arm/selection.ml index ce36a4624343..bbcd53428fd9 100644 --- a/asmcomp/arm/selection.ml +++ b/asmcomp/arm/selection.ml @@ -54,7 +54,7 @@ method select_addressing = function (Iindexed n, Cop(Cadda, [arg1; arg2])) | arg -> (Iindexed 0, arg) - + method select_shift_arith op shiftop shiftrevop args = match args with [arg1; Cop(Clsl, [arg2; Cconst_int n])] @@ -90,7 +90,7 @@ method select_operation op args = | _ -> self#select_shift_arith op Ishiftsub Ishiftsubrev args end - | Cmuli -> (* no multiply immediate *) + | Cmuli -> (* no multiply immediate *) (Iintop Imul, args) | Cdivi -> begin match args with @@ -109,8 +109,8 @@ method select_operation op args = | Ccheckbound -> begin match args with [Cop(Clsr, [arg1; Cconst_int n]); arg2] - when n > 0 && n < 32 && not(is_intconst arg2) -> - (Ispecific(Ishiftcheckbound n), [arg1; arg2]) + when n > 0 && n < 32 && not(is_intconst arg2) -> + (Ispecific(Ishiftcheckbound n), [arg1; arg2]) | _ -> super#select_operation op args end diff --git a/asmrun/power-rhapsody.S b/asmrun/power-rhapsody.S index 162886bf3654..0db410369af3 100644 --- a/asmrun/power-rhapsody.S +++ b/asmrun/power-rhapsody.S @@ -12,15 +12,15 @@ /* $Id$ */ -.macro Addrglobal /* reg, glob */ +.macro Addrglobal /* reg, glob */ addis $0, 0, ha16($1) addi $0, $0, lo16($1) .endmacro -.macro Loadglobal /* reg,glob,tmp */ +.macro Loadglobal /* reg,glob,tmp */ addis $2, 0, ha16($1) lwz $0, lo16($1)($2) .endmacro -.macro Storeglobal /* reg,glob,tmp */ +.macro Storeglobal /* reg,glob,tmp */ addis $2, 0, ha16($1) stw $0, lo16($1)($2) .endmacro @@ -204,7 +204,7 @@ _caml_c_call: Storeglobal r12, _caml_last_return_address, r11 /* Return to caller */ blr - + /* Raise an exception from C */ .globl _raise_caml_exception @@ -296,7 +296,7 @@ L103: stw r11, 4(r1) mr r29, r1 /* Reload allocation pointers */ - Loadglobal r31, _young_ptr, r11 + Loadglobal r31, _young_ptr, r11 Loadglobal r30, _young_limit, r11 /* Say we are back into Caml code */ li r0, 0 @@ -314,9 +314,9 @@ L106: lwz r9, 0(r1) lwz r10, 4(r1) lwz r11, 8(r1) - Storeglobal r9, _caml_bottom_of_stack, r12 - Storeglobal r10, _caml_last_return_address, r12 - Storeglobal r11, _caml_gc_regs, r12 + Storeglobal r9, _caml_bottom_of_stack, r12 + Storeglobal r10, _caml_last_return_address, r12 + Storeglobal r11, _caml_gc_regs, r12 addi r1, r1, 16 /* Update allocation pointer */ Storeglobal r31, _young_ptr, r11 @@ -392,7 +392,7 @@ _callback2_exn: mr r5, r0 Addrglobal r12, _caml_apply2 b L102 - + .globl _callback3_exn _callback3_exn: mr r0, r3 /* Closure */