ocaml/asmcomp/mach.ml

164 lines
5.3 KiB
OCaml

(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* Representation of machine code by sequences of pseudoinstructions *)
type integer_comparison =
Isigned of Cmm.integer_comparison
| Iunsigned of Cmm.integer_comparison
type integer_operation =
Iadd | Isub | Imul | Imulh | Idiv | Imod
| Iand | Ior | Ixor | Ilsl | Ilsr | Iasr
| Icomp of integer_comparison
| Icheckbound
type float_comparison = Cmm.float_comparison
type test =
Itruetest
| Ifalsetest
| Iinttest of integer_comparison
| Iinttest_imm of integer_comparison * int
| Ifloattest of float_comparison
| Ioddtest
| Ieventest
type operation =
Imove
| Ispill
| Ireload
| Iconst_int of nativeint
| Iconst_float of int64
| Iconst_symbol of string
| Icall_ind
| Icall_imm of { func : string; }
| Itailcall_ind
| Itailcall_imm of { func : string; }
| Iextcall of { func : string;
ty_res : Cmm.machtype; ty_args : Cmm.exttype list;
alloc : bool; }
| Istackoffset of int
| Iload of Cmm.memory_chunk * Arch.addressing_mode
| Istore of Cmm.memory_chunk * Arch.addressing_mode * bool
| Ialloc of { bytes : int; dbginfo : Debuginfo.alloc_dbginfo; }
| Iintop of integer_operation
| Iintop_imm of integer_operation * int
| Inegf | Iabsf | Iaddf | Isubf | Imulf | Idivf
| Ifloatofint | Iintoffloat
| Ispecific of Arch.specific_operation
| Iname_for_debugger of { ident : Backend_var.t; which_parameter : int option;
provenance : unit option; is_assignment : bool; }
type instruction =
{ desc: instruction_desc;
next: instruction;
arg: Reg.t array;
res: Reg.t array;
dbg: Debuginfo.t;
mutable live: Reg.Set.t;
mutable available_before: Reg_availability_set.t;
mutable available_across: Reg_availability_set.t option;
}
and instruction_desc =
Iend
| Iop of operation
| Ireturn
| Iifthenelse of test * instruction * instruction
| Iswitch of int array * instruction array
| Icatch of Cmm.rec_flag * (int * instruction) list * instruction
| Iexit of int
| Itrywith of instruction * instruction
| Iraise of Lambda.raise_kind
type fundecl =
{ fun_name: string;
fun_args: Reg.t array;
fun_body: instruction;
fun_codegen_options : Cmm.codegen_option list;
fun_dbg : Debuginfo.t;
fun_num_stack_slots: int array;
fun_contains_calls: bool;
}
let rec dummy_instr =
{ desc = Iend;
next = dummy_instr;
arg = [||];
res = [||];
dbg = Debuginfo.none;
live = Reg.Set.empty;
available_before = Reg_availability_set.Ok Reg_with_debug_info.Set.empty;
available_across = None;
}
let end_instr () =
{ desc = Iend;
next = dummy_instr;
arg = [||];
res = [||];
dbg = Debuginfo.none;
live = Reg.Set.empty;
available_before = Reg_availability_set.Ok Reg_with_debug_info.Set.empty;
available_across = None;
}
let instr_cons d a r n =
{ desc = d; next = n; arg = a; res = r;
dbg = Debuginfo.none; live = Reg.Set.empty;
available_before = Reg_availability_set.Ok Reg_with_debug_info.Set.empty;
available_across = None;
}
let instr_cons_debug d a r dbg n =
{ desc = d; next = n; arg = a; res = r; dbg = dbg; live = Reg.Set.empty;
available_before = Reg_availability_set.Ok Reg_with_debug_info.Set.empty;
available_across = None;
}
let rec instr_iter f i =
match i.desc with
Iend -> ()
| _ ->
f i;
match i.desc with
Iend -> ()
| Ireturn | Iop Itailcall_ind | Iop(Itailcall_imm _) -> ()
| Iifthenelse(_tst, ifso, ifnot) ->
instr_iter f ifso; instr_iter f ifnot; instr_iter f i.next
| Iswitch(_index, cases) ->
for i = 0 to Array.length cases - 1 do
instr_iter f cases.(i)
done;
instr_iter f i.next
| Icatch(_, handlers, body) ->
instr_iter f body;
List.iter (fun (_n, handler) -> instr_iter f handler) handlers;
instr_iter f i.next
| Iexit _ -> ()
| Itrywith(body, handler) ->
instr_iter f body; instr_iter f handler; instr_iter f i.next
| Iraise _ -> ()
| _ ->
instr_iter f i.next
let operation_can_raise op =
match op with
| Icall_ind | Icall_imm _ | Iextcall _
| Iintop (Icheckbound) | Iintop_imm (Icheckbound, _)
| Ialloc _ -> true
| _ -> false