Skip to content

Commit

Permalink
tabs -> spaces
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2639 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
Damien Doligez committed Nov 29, 1999
1 parent 44c244d commit ddc7d63
Show file tree
Hide file tree
Showing 4 changed files with 16 additions and 16 deletions.
2 changes: 1 addition & 1 deletion asmcomp/arm/emit.mlp
Expand Up @@ -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`;
Expand Down
4 changes: 2 additions & 2 deletions asmcomp/arm/proc.ml
Expand Up @@ -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"
|]
Expand Down Expand Up @@ -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
Expand Down
8 changes: 4 additions & 4 deletions asmcomp/arm/selection.ml
Expand Up @@ -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])]
Expand Down Expand Up @@ -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
Expand All @@ -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
Expand Down
18 changes: 9 additions & 9 deletions asmrun/power-rhapsody.S
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand All @@ -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
Expand Down Expand Up @@ -392,7 +392,7 @@ _callback2_exn:
mr r5, r0
Addrglobal r12, _caml_apply2
b L102

.globl _callback3_exn
_callback3_exn:
mr r0, r3 /* Closure */
Expand Down

0 comments on commit ddc7d63

Please sign in to comment.