forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathselectgen.mli
170 lines (148 loc) · 7.05 KB
/
selectgen.mli
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
(**************************************************************************)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
(* Selection of pseudo-instructions, assignment of pseudo-registers,
sequentialization. *)
type environment
val env_add
: ?mut:Asttypes.mutable_flag
-> Backend_var.With_provenance.t
-> Reg.t array
-> environment
-> environment
val env_find : Backend_var.t -> environment -> Reg.t array
val size_expr : environment -> Cmm.expression -> int
module Effect : sig
type t =
| None
| Raise
| Arbitrary
end
module Coeffect : sig
type t =
| None
| Read_mutable
| Arbitrary
end
module Effect_and_coeffect : sig
type t
val none : t
val arbitrary : t
val effect : t -> Effect.t
val coeffect : t -> Coeffect.t
val effect_only : Effect.t -> t
val coeffect_only : Coeffect.t -> t
val join : t -> t -> t
val join_list_map : 'a list -> ('a -> t) -> t
end
class virtual selector_generic : object
(* The following methods must or can be overridden by the processor
description *)
method is_immediate : Mach.integer_operation -> int -> bool
(* Must be overridden to indicate whether a constant is a suitable
immediate operand to the given integer arithmetic instruction.
The default implementation handles shifts by immediate amounts,
but produces no immediate operations otherwise. *)
method virtual is_immediate_test : Mach.integer_comparison -> int -> bool
(* Must be defined to indicate whether a constant is a suitable
immediate operand to the given integer test *)
method virtual select_addressing :
Cmm.memory_chunk -> Cmm.expression -> Arch.addressing_mode * Cmm.expression
(* Must be defined to select addressing modes *)
method is_simple_expr: Cmm.expression -> bool
method effects_of : Cmm.expression -> Effect_and_coeffect.t
(* Can be overridden to reflect special extcalls known to be pure *)
method select_operation :
Cmm.operation ->
Cmm.expression list ->
Debuginfo.t ->
Mach.operation * Cmm.expression list
(* Can be overridden to deal with special arithmetic instructions *)
method select_condition : Cmm.expression -> Mach.test * Cmm.expression
(* Can be overridden to deal with special test instructions *)
method select_store :
bool -> Arch.addressing_mode -> Cmm.expression ->
Mach.operation * Cmm.expression
(* Can be overridden to deal with special store constant instructions *)
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 overridden if float values are stored as pairs of
integer registers. *)
method insert_op :
environment -> Mach.operation -> Reg.t array -> Reg.t array -> Reg.t array
(* Can be overridden to deal with 2-address instructions
or instructions with hardwired input/output registers *)
method insert_op_debug :
environment -> Mach.operation -> Debuginfo.t -> Reg.t array
-> Reg.t array -> Reg.t array
(* Can be overridden to deal with 2-address instructions
or instructions with hardwired input/output registers *)
method insert_move_extcall_arg :
environment -> Cmm.exttype -> Reg.t array -> Reg.t array -> unit
(* Can be overridden to deal with unusual unboxed calling conventions,
e.g. on a 64-bit platform, passing unboxed 32-bit arguments
in 32-bit stack slots. *)
method emit_extcall_args :
environment -> Cmm.exttype list -> Cmm.expression list -> Reg.t array * int
(* Can be overridden to deal with stack-based calling conventions *)
method emit_stores :
environment -> Cmm.expression list -> Reg.t array -> unit
(* Fill a freshly allocated block. Can be overridden for architectures
that do not provide Arch.offset_addressing. *)
method mark_call : unit
(* informs the code emitter that the current function is non-leaf:
it may perform a (non-tail) call; by default, sets
[contains_calls := true] *)
method mark_tailcall : unit
(* informs the code emitter that the current function may end with
a tail-call; by default, does nothing *)
method mark_c_tailcall : unit
(* informs the code emitter that the current function may call
a C function that never returns; by default, does nothing.
It is unnecessary to save the stack pointer in this situation
(which is the main purpose of tracking leaf functions) but some
architectures still need to ensure that the stack is properly
aligned when the C function is called. This is achieved by
overloading this method to set [contains_calls := true] *)
method mark_instr : Mach.instruction_desc -> unit
(* dispatches on instructions to call one of the marking function
above; overloading this is useful if Ispecific instructions need
marking *)
(* The following method is the entry point and should not be overridden. *)
method emit_fundecl : Cmm.fundecl -> Mach.fundecl
(* The following methods should not be overridden. They cannot be
declared "private" in the current implementation because they
are not always applied to "self", but ideally they should be private. *)
method extract : Mach.instruction
method insert :
environment -> Mach.instruction_desc -> Reg.t array -> Reg.t array -> unit
method insert_debug :
environment -> Mach.instruction_desc -> Debuginfo.t ->
Reg.t array -> Reg.t array -> unit
method insert_move : environment -> Reg.t -> Reg.t -> unit
method insert_move_args :
environment -> Reg.t array -> Reg.t array -> int -> unit
method insert_move_results :
environment -> Reg.t array -> Reg.t array -> int -> unit
method insert_moves : environment -> Reg.t array -> Reg.t array -> unit
method emit_expr :
environment -> Cmm.expression -> Reg.t array option
method emit_tail : environment -> Cmm.expression -> unit
(* [contains_calls] is declared as a reference instance variable,
instead of a mutable boolean instance variable,
because the traversal uses functional object copies. *)
val contains_calls : bool ref
end
val reset : unit -> unit