forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
mach.mli
119 lines (107 loc) · 4.2 KB
/
mach.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
(**************************************************************************)
(* *)
(* 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;
stack_ofs : int; }
| Istackoffset of int
| Iload of { memory_chunk : Cmm.memory_chunk;
addressing_mode : Arch.addressing_mode;
mutability : Asttypes.mutable_flag;
is_atomic : bool }
| Istore of Cmm.memory_chunk * Arch.addressing_mode * bool
(* false = initialization, true = assignment *)
| 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
| Iopaque
| Ispecific of Arch.specific_operation
| Ipoll of { return_label: Cmm.label option }
| Idls_get
type instruction =
{ desc: instruction_desc;
next: instruction;
arg: Reg.t array;
res: Reg.t array;
dbg: Debuginfo.t;
mutable live: Reg.Set.t
}
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_poll: Lambda.poll_attribute;
fun_num_stack_slots: int array;
fun_contains_calls: bool;
}
val dummy_instr: instruction
val end_instr: unit -> instruction
val instr_cons:
instruction_desc -> Reg.t array -> Reg.t array -> instruction ->
instruction
val instr_cons_debug:
instruction_desc -> Reg.t array -> Reg.t array -> Debuginfo.t ->
instruction -> instruction
val instr_iter: (instruction -> unit) -> instruction -> unit
val operation_is_pure : operation -> bool
(** Returns [true] if the given operation only produces a result
in its destination registers, but has no side effects whatsoever:
it doesn't raise exceptions, it doesn't modify already-allocated
blocks, it doesn't adjust the stack frame, etc. *)
val operation_can_raise : operation -> bool
(** Returns [true] if the given operation can raise an exception. *)