1997-07-24 04:49:12 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Objective Caml *)
|
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1997-07-24 04:49:12 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
|
|
|
(* Selection of pseudo-instructions, assignment of pseudo-registers,
|
|
|
|
sequentialization. *)
|
|
|
|
|
|
|
|
type environment = (Ident.t, Reg.t array) Tbl.t
|
|
|
|
|
|
|
|
val size_expr : environment -> Cmm.expression -> int
|
|
|
|
|
1998-06-24 12:22:26 -07:00
|
|
|
class virtual selector_generic : object
|
1997-07-24 04:49:12 -07:00
|
|
|
(* The following methods must or can be overriden by the processor
|
|
|
|
description *)
|
1998-06-24 12:22:26 -07:00
|
|
|
method virtual is_immediate : int -> bool
|
1997-07-24 04:49:12 -07:00
|
|
|
(* Must be defined to indicate whether a constant is a suitable
|
|
|
|
immediate operand to arithmetic instructions *)
|
1998-06-24 12:22:26 -07:00
|
|
|
method virtual select_addressing :
|
1997-07-24 04:49:12 -07:00
|
|
|
Cmm.expression -> Arch.addressing_mode * Cmm.expression
|
|
|
|
(* Must be defined to select addressing modes *)
|
2006-04-16 16:28:22 -07:00
|
|
|
method is_simple_expr: Cmm.expression -> bool
|
|
|
|
(* Can be overriden to reflect special extcalls known to be pure *)
|
1997-07-24 04:49:12 -07:00
|
|
|
method select_operation :
|
|
|
|
Cmm.operation ->
|
|
|
|
Cmm.expression list -> Mach.operation * Cmm.expression list
|
|
|
|
(* Can be overriden to deal with special arithmetic instructions *)
|
|
|
|
method select_condition : Cmm.expression -> Mach.test * Cmm.expression
|
|
|
|
(* Can be overriden to deal with special test instructions *)
|
|
|
|
method select_store :
|
|
|
|
Arch.addressing_mode -> Cmm.expression -> Mach.operation * Cmm.expression
|
|
|
|
(* Can be overriden to deal with special store constant instructions *)
|
2009-03-31 02:44:50 -07:00
|
|
|
method regs_for : Cmm.machtype -> Reg.t array
|
|
|
|
(* Return an array of fresh registers of the given type.
|
|
|
|
Default implementation is like Reg.createv.
|
|
|
|
Can be overriden if float values are stored as pairs of
|
|
|
|
integer registers. *)
|
1997-07-24 04:49:12 -07:00
|
|
|
method insert_op :
|
|
|
|
Mach.operation -> Reg.t array -> Reg.t array -> Reg.t array
|
|
|
|
(* Can be overriden to deal with 2-address instructions
|
|
|
|
or instructions with hardwired input/output registers *)
|
2007-01-29 04:11:18 -08:00
|
|
|
method insert_op_debug :
|
|
|
|
Mach.operation -> Debuginfo.t -> Reg.t array -> Reg.t array -> Reg.t array
|
|
|
|
(* Can be overriden to deal with 2-address instructions
|
|
|
|
or instructions with hardwired input/output registers *)
|
1997-07-24 04:49:12 -07:00
|
|
|
method emit_extcall_args :
|
|
|
|
environment -> Cmm.expression list -> Reg.t array * int
|
|
|
|
(* Can be overriden to deal with stack-based calling conventions *)
|
2000-06-29 04:44:36 -07:00
|
|
|
method emit_stores :
|
|
|
|
environment -> Cmm.expression list -> Reg.t array -> unit
|
|
|
|
(* Fill a freshly allocated block. Can be overriden for architectures
|
|
|
|
that do not provide Arch.offset_addressing. *)
|
1997-07-24 04:49:12 -07:00
|
|
|
|
1997-11-06 09:25:24 -08:00
|
|
|
(* The following method is the entry point and should not be overriden *)
|
1997-07-24 04:49:12 -07:00
|
|
|
method emit_fundecl : Cmm.fundecl -> Mach.fundecl
|
1997-11-06 09:25:24 -08:00
|
|
|
|
|
|
|
(* The following methods should not be overriden. They cannot be
|
|
|
|
declared "private" in the current implementation because they
|
|
|
|
are not always applied to "self", but ideally they should be private. *)
|
1997-07-24 04:49:12 -07:00
|
|
|
method extract : Mach.instruction
|
|
|
|
method insert : Mach.instruction_desc -> Reg.t array -> Reg.t array -> unit
|
2007-01-29 04:11:18 -08:00
|
|
|
method insert_debug : Mach.instruction_desc -> Debuginfo.t ->
|
|
|
|
Reg.t array -> Reg.t array -> unit
|
1997-07-24 04:49:12 -07:00
|
|
|
method insert_move : Reg.t -> Reg.t -> unit
|
|
|
|
method insert_move_args : Reg.t array -> Reg.t array -> int -> unit
|
|
|
|
method insert_move_results : Reg.t array -> Reg.t array -> int -> unit
|
|
|
|
method insert_moves : Reg.t array -> Reg.t array -> unit
|
1997-11-06 09:25:24 -08:00
|
|
|
method emit_expr :
|
2002-11-04 08:25:09 -08:00
|
|
|
(Ident.t, Reg.t array) Tbl.t -> Cmm.expression -> Reg.t array option
|
1997-11-06 09:25:24 -08:00
|
|
|
method emit_tail : (Ident.t, Reg.t array) Tbl.t -> Cmm.expression -> unit
|
1997-07-24 04:49:12 -07:00
|
|
|
end
|