]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/asmcomp/selectgen.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / asmcomp / selectgen.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: selectgen.mli 7812 2007-01-29 12:11:18Z xleroy $ *)
14
15 (* Selection of pseudo-instructions, assignment of pseudo-registers,
16    sequentialization. *)
17
18 type environment = (Ident.t, Reg.t array) Tbl.t
19
20 val size_expr : environment -> Cmm.expression -> int
21
22 class virtual selector_generic : object
23   (* The following methods must or can be overriden by the processor
24      description *)
25   method virtual is_immediate : int -> bool
26     (* Must be defined to indicate whether a constant is a suitable
27        immediate operand to arithmetic instructions *)
28   method virtual select_addressing :
29     Cmm.expression -> Arch.addressing_mode * Cmm.expression
30     (* Must be defined to select addressing modes *)
31   method is_simple_expr: Cmm.expression -> bool
32     (* Can be overriden to reflect special extcalls known to be pure *)
33   method select_operation :
34     Cmm.operation ->
35     Cmm.expression list -> Mach.operation * Cmm.expression list
36     (* Can be overriden to deal with special arithmetic instructions *)
37   method select_condition : Cmm.expression -> Mach.test * Cmm.expression
38     (* Can be overriden to deal with special test instructions *)
39   method select_store :
40     Arch.addressing_mode -> Cmm.expression -> Mach.operation * Cmm.expression
41     (* Can be overriden to deal with special store constant instructions *)
42   method insert_op :
43     Mach.operation -> Reg.t array -> Reg.t array -> Reg.t array
44     (* Can be overriden to deal with 2-address instructions
45        or instructions with hardwired input/output registers *)
46   method insert_op_debug :
47     Mach.operation -> Debuginfo.t -> Reg.t array -> Reg.t array -> Reg.t array
48     (* Can be overriden to deal with 2-address instructions
49        or instructions with hardwired input/output registers *)
50   method emit_extcall_args :
51     environment -> Cmm.expression list -> Reg.t array * int
52     (* Can be overriden to deal with stack-based calling conventions *)
53   method emit_stores :
54     environment -> Cmm.expression list -> Reg.t array -> unit
55     (* Fill a freshly allocated block.  Can be overriden for architectures
56        that do not provide Arch.offset_addressing. *)
57
58   (* The following method is the entry point and should not be overriden *)
59   method emit_fundecl : Cmm.fundecl -> Mach.fundecl
60   
61   (* The following methods should not be overriden.  They cannot be
62      declared "private" in the current implementation because they
63      are not always applied to "self", but ideally they should be private. *)
64   method extract : Mach.instruction
65   method insert : Mach.instruction_desc -> Reg.t array -> Reg.t array -> unit
66   method insert_debug : Mach.instruction_desc -> Debuginfo.t ->
67                                         Reg.t array -> Reg.t array -> unit
68   method insert_move : Reg.t -> Reg.t -> unit
69   method insert_move_args : Reg.t array -> Reg.t array -> int -> unit
70   method insert_move_results : Reg.t array -> Reg.t array -> int -> unit
71   method insert_moves : Reg.t array -> Reg.t array -> unit
72   method emit_expr :
73     (Ident.t, Reg.t array) Tbl.t -> Cmm.expression -> Reg.t array option
74   method emit_tail : (Ident.t, Reg.t array) Tbl.t -> Cmm.expression -> unit
75 end