1 //! This module exposes the machine-specific backend definition pieces.
2 //!
3 //! The MachInst infrastructure is the compiler backend, from CLIF
4 //! (ir::Function) to machine code. The purpose of this infrastructure is, at a
5 //! high level, to do instruction selection/lowering (to machine instructions),
6 //! register allocation, and then perform all the fixups to branches, constant
7 //! data references, etc., needed to actually generate machine code.
8 //!
9 //! The container for machine instructions, at various stages of construction,
10 //! is the `VCode` struct. We refer to a sequence of machine instructions organized
11 //! into basic blocks as "vcode". This is short for "virtual-register code", though
12 //! it's a bit of a misnomer because near the end of the pipeline, vcode has all
13 //! real registers. Nevertheless, the name is catchy and we like it.
14 //!
15 //! The compilation pipeline, from an `ir::Function` (already optimized as much as
16 //! you like by machine-independent optimization passes) onward, is as follows.
17 //! (N.B.: though we show the VCode separately at each stage, the passes
18 //! mutate the VCode in place; these are not separate copies of the code.)
19 //!
20 //! ```plain
21 //!
22 //!     ir::Function                (SSA IR, machine-independent opcodes)
23 //!         |
24 //!         |  [lower]
25 //!         |
26 //!     VCode<arch_backend::Inst>   (machine instructions:
27 //!         |                        - mostly virtual registers.
28 //!         |                        - cond branches in two-target form.
29 //!         |                        - branch targets are block indices.
30 //!         |                        - in-memory constants held by insns,
31 //!         |                          with unknown offsets.
32 //!         |                        - critical edges (actually all edges)
33 //!         |                          are split.)
34 //!         | [regalloc]
35 //!         |
36 //!     VCode<arch_backend::Inst>   (machine instructions:
37 //!         |                        - all real registers.
38 //!         |                        - new instruction sequence returned
39 //!         |                          out-of-band in RegAllocResult.
40 //!         |                        - instruction sequence has spills,
41 //!         |                          reloads, and moves inserted.
42 //!         |                        - other invariants same as above.)
43 //!         |
44 //!         | [preamble/postamble]
45 //!         |
46 //!     VCode<arch_backend::Inst>   (machine instructions:
47 //!         |                        - stack-frame size known.
48 //!         |                        - out-of-band instruction sequence
49 //!         |                          has preamble prepended to entry
50 //!         |                          block, and postamble injected before
51 //!         |                          every return instruction.
52 //!         |                        - all symbolic stack references to
53 //!         |                          stackslots and spillslots are resolved
54 //!         |                          to concrete FP-offset mem addresses.)
55 //!         | [block/insn ordering]
56 //!         |
57 //!     VCode<arch_backend::Inst>   (machine instructions:
58 //!         |                        - vcode.final_block_order is filled in.
59 //!         |                        - new insn sequence from regalloc is
60 //!         |                          placed back into vcode and block
61 //!         |                          boundaries are updated.)
62 //!         | [redundant branch/block
63 //!         |  removal]
64 //!         |
65 //!     VCode<arch_backend::Inst>   (machine instructions:
66 //!         |                        - all blocks that were just an
67 //!         |                          unconditional branch are removed.)
68 //!         |
69 //!         | [branch finalization
70 //!         |  (fallthroughs)]
71 //!         |
72 //!     VCode<arch_backend::Inst>   (machine instructions:
73 //!         |                        - all branches are in lowered one-
74 //!         |                          target form, but targets are still
75 //!         |                          block indices.)
76 //!         |
77 //!         | [branch finalization
78 //!         |  (offsets)]
79 //!         |
80 //!     VCode<arch_backend::Inst>   (machine instructions:
81 //!         |                        - all branch offsets from start of
82 //!         |                          function are known, and all branches
83 //!         |                          have resolved-offset targets.)
84 //!         |
85 //!         | [MemArg finalization]
86 //!         |
87 //!     VCode<arch_backend::Inst>   (machine instructions:
88 //!         |                        - all MemArg references to the constant
89 //!         |                          pool are replaced with offsets.
90 //!         |                        - all constant-pool data is collected
91 //!         |                          in the VCode.)
92 //!         |
93 //!         | [binary emission]
94 //!         |
95 //!     Vec<u8>                     (machine code!)
96 //!
97 //! ```
98 
99 use crate::binemit::{CodeInfo, CodeOffset};
100 use crate::ir::condcodes::IntCC;
101 use crate::ir::{Function, Type};
102 use crate::result::CodegenResult;
103 use crate::settings::Flags;
104 
105 use alloc::boxed::Box;
106 use alloc::vec::Vec;
107 use core::fmt::Debug;
108 use regalloc::RegUsageCollector;
109 use regalloc::{
110     RealReg, RealRegUniverse, Reg, RegClass, RegUsageMapper, SpillSlot, VirtualReg, Writable,
111 };
112 use smallvec::SmallVec;
113 use std::string::String;
114 use target_lexicon::Triple;
115 
116 pub mod lower;
117 pub use lower::*;
118 pub mod vcode;
119 pub use vcode::*;
120 pub mod compile;
121 pub use compile::*;
122 pub mod blockorder;
123 pub use blockorder::*;
124 pub mod abi;
125 pub use abi::*;
126 pub mod pretty_print;
127 pub use pretty_print::*;
128 pub mod buffer;
129 pub use buffer::*;
130 pub mod adapter;
131 pub use adapter::*;
132 
133 /// A machine instruction.
134 pub trait MachInst: Clone + Debug {
135     /// Return the registers referenced by this machine instruction along with
136     /// the modes of reference (use, def, modify).
get_regs(&self, collector: &mut RegUsageCollector)137     fn get_regs(&self, collector: &mut RegUsageCollector);
138 
139     /// Map virtual registers to physical registers using the given virt->phys
140     /// maps corresponding to the program points prior to, and after, this instruction.
map_regs<RUM: RegUsageMapper>(&mut self, maps: &RUM)141     fn map_regs<RUM: RegUsageMapper>(&mut self, maps: &RUM);
142 
143     /// If this is a simple move, return the (source, destination) tuple of registers.
is_move(&self) -> Option<(Writable<Reg>, Reg)>144     fn is_move(&self) -> Option<(Writable<Reg>, Reg)>;
145 
146     /// Is this a terminator (branch or ret)? If so, return its type
147     /// (ret/uncond/cond) and target if applicable.
is_term<'a>(&'a self) -> MachTerminator<'a>148     fn is_term<'a>(&'a self) -> MachTerminator<'a>;
149 
150     /// Returns true if the instruction is an epilogue placeholder.
is_epilogue_placeholder(&self) -> bool151     fn is_epilogue_placeholder(&self) -> bool;
152 
153     /// Generate a move.
gen_move(to_reg: Writable<Reg>, from_reg: Reg, ty: Type) -> Self154     fn gen_move(to_reg: Writable<Reg>, from_reg: Reg, ty: Type) -> Self;
155 
156     /// Generate a constant into a reg.
gen_constant(to_reg: Writable<Reg>, value: u64, ty: Type) -> SmallVec<[Self; 4]>157     fn gen_constant(to_reg: Writable<Reg>, value: u64, ty: Type) -> SmallVec<[Self; 4]>;
158 
159     /// Generate a zero-length no-op.
gen_zero_len_nop() -> Self160     fn gen_zero_len_nop() -> Self;
161 
162     /// Possibly operate on a value directly in a spill-slot rather than a
163     /// register. Useful if the machine has register-memory instruction forms
164     /// (e.g., add directly from or directly to memory), like x86.
maybe_direct_reload(&self, reg: VirtualReg, slot: SpillSlot) -> Option<Self>165     fn maybe_direct_reload(&self, reg: VirtualReg, slot: SpillSlot) -> Option<Self>;
166 
167     /// Determine a register class to store the given Cranelift type.
168     /// May return an error if the type isn't supported by this backend.
rc_for_type(ty: Type) -> CodegenResult<RegClass>169     fn rc_for_type(ty: Type) -> CodegenResult<RegClass>;
170 
171     /// Generate a jump to another target. Used during lowering of
172     /// control flow.
gen_jump(target: MachLabel) -> Self173     fn gen_jump(target: MachLabel) -> Self;
174 
175     /// Generate a NOP. The `preferred_size` parameter allows the caller to
176     /// request a NOP of that size, or as close to it as possible. The machine
177     /// backend may return a NOP whose binary encoding is smaller than the
178     /// preferred size, but must not return a NOP that is larger. However,
179     /// the instruction must have a nonzero size.
gen_nop(preferred_size: usize) -> Self180     fn gen_nop(preferred_size: usize) -> Self;
181 
182     /// Get the register universe for this backend.
reg_universe(flags: &Flags) -> RealRegUniverse183     fn reg_universe(flags: &Flags) -> RealRegUniverse;
184 
185     /// Align a basic block offset (from start of function).  By default, no
186     /// alignment occurs.
align_basic_block(offset: CodeOffset) -> CodeOffset187     fn align_basic_block(offset: CodeOffset) -> CodeOffset {
188         offset
189     }
190 
191     /// What is the worst-case instruction size emitted by this instruction type?
worst_case_size() -> CodeOffset192     fn worst_case_size() -> CodeOffset;
193 
194     /// A label-use kind: a type that describes the types of label references that
195     /// can occur in an instruction.
196     type LabelUse: MachInstLabelUse;
197 }
198 
199 /// A descriptor of a label reference (use) in an instruction set.
200 pub trait MachInstLabelUse: Clone + Copy + Debug + Eq {
201     /// Required alignment for any veneer. Usually the required instruction
202     /// alignment (e.g., 4 for a RISC with 32-bit instructions, or 1 for x86).
203     const ALIGN: CodeOffset;
204 
205     /// What is the maximum PC-relative range (positive)? E.g., if `1024`, a
206     /// label-reference fixup at offset `x` is valid if the label resolves to `x
207     /// + 1024`.
max_pos_range(self) -> CodeOffset208     fn max_pos_range(self) -> CodeOffset;
209     /// What is the maximum PC-relative range (negative)? This is the absolute
210     /// value; i.e., if `1024`, then a label-reference fixup at offset `x` is
211     /// valid if the label resolves to `x - 1024`.
max_neg_range(self) -> CodeOffset212     fn max_neg_range(self) -> CodeOffset;
213     /// What is the size of code-buffer slice this label-use needs to patch in
214     /// the label's value?
patch_size(self) -> CodeOffset215     fn patch_size(self) -> CodeOffset;
216     /// Perform a code-patch, given the offset into the buffer of this label use
217     /// and the offset into the buffer of the label's definition.
218     /// It is guaranteed that, given `delta = offset - label_offset`, we will
219     /// have `offset >= -self.max_neg_range()` and `offset <=
220     /// self.max_pos_range()`.
patch(self, buffer: &mut [u8], use_offset: CodeOffset, label_offset: CodeOffset)221     fn patch(self, buffer: &mut [u8], use_offset: CodeOffset, label_offset: CodeOffset);
222     /// Can the label-use be patched to a veneer that supports a longer range?
223     /// Usually valid for jumps (a short-range jump can jump to a longer-range
224     /// jump), but not for e.g. constant pool references, because the constant
225     /// load would require different code (one more level of indirection).
supports_veneer(self) -> bool226     fn supports_veneer(self) -> bool;
227     /// How many bytes are needed for a veneer?
veneer_size(self) -> CodeOffset228     fn veneer_size(self) -> CodeOffset;
229     /// Generate a veneer. The given code-buffer slice is `self.veneer_size()`
230     /// bytes long at offset `veneer_offset` in the buffer. The original
231     /// label-use will be patched to refer to this veneer's offset.  A new
232     /// (offset, LabelUse) is returned that allows the veneer to use the actual
233     /// label. For veneers to work properly, it is expected that the new veneer
234     /// has a larger range; on most platforms this probably means either a
235     /// "long-range jump" (e.g., on ARM, the 26-bit form), or if already at that
236     /// stage, a jump that supports a full 32-bit range, for example.
generate_veneer(self, buffer: &mut [u8], veneer_offset: CodeOffset) -> (CodeOffset, Self)237     fn generate_veneer(self, buffer: &mut [u8], veneer_offset: CodeOffset) -> (CodeOffset, Self);
238 }
239 
240 /// Describes a block terminator (not call) in the vcode, when its branches
241 /// have not yet been finalized (so a branch may have two targets).
242 #[derive(Clone, Debug, PartialEq, Eq)]
243 pub enum MachTerminator<'a> {
244     /// Not a terminator.
245     None,
246     /// A return instruction.
247     Ret,
248     /// An unconditional branch to another block.
249     Uncond(MachLabel),
250     /// A conditional branch to one of two other blocks.
251     Cond(MachLabel, MachLabel),
252     /// An indirect branch with known possible targets.
253     Indirect(&'a [MachLabel]),
254 }
255 
256 /// A trait describing the ability to encode a MachInst into binary machine code.
257 pub trait MachInstEmit: MachInst {
258     /// Persistent state carried across `emit` invocations.
259     type State: Default + Clone + Debug;
260     /// Emit the instruction.
emit(&self, code: &mut MachBuffer<Self>, flags: &Flags, state: &mut Self::State)261     fn emit(&self, code: &mut MachBuffer<Self>, flags: &Flags, state: &mut Self::State);
262 }
263 
264 /// The result of a `MachBackend::compile_function()` call. Contains machine
265 /// code (as bytes) and a disassembly, if requested.
266 pub struct MachCompileResult {
267     /// Machine code.
268     pub buffer: MachBufferFinalized,
269     /// Size of stack frame, in bytes.
270     pub frame_size: u32,
271     /// Disassembly, if requested.
272     pub disasm: Option<String>,
273 }
274 
275 impl MachCompileResult {
276     /// Get a `CodeInfo` describing section sizes from this compilation result.
code_info(&self) -> CodeInfo277     pub fn code_info(&self) -> CodeInfo {
278         let code_size = self.buffer.total_size();
279         CodeInfo {
280             code_size,
281             jumptables_size: 0,
282             rodata_size: 0,
283             total_size: code_size,
284         }
285     }
286 }
287 
288 /// Top-level machine backend trait, which wraps all monomorphized code and
289 /// allows a virtual call from the machine-independent `Function::compile()`.
290 pub trait MachBackend {
291     /// Compile the given function.
compile_function( &self, func: &Function, want_disasm: bool, ) -> CodegenResult<MachCompileResult>292     fn compile_function(
293         &self,
294         func: &Function,
295         want_disasm: bool,
296     ) -> CodegenResult<MachCompileResult>;
297 
298     /// Return flags for this backend.
flags(&self) -> &Flags299     fn flags(&self) -> &Flags;
300 
301     /// Return triple for this backend.
triple(&self) -> Triple302     fn triple(&self) -> Triple;
303 
304     /// Return name for this backend.
name(&self) -> &'static str305     fn name(&self) -> &'static str;
306 
307     /// Return the register universe for this backend.
reg_universe(&self) -> &RealRegUniverse308     fn reg_universe(&self) -> &RealRegUniverse;
309 
310     /// Machine-specific condcode info needed by TargetIsa.
unsigned_add_overflow_condition(&self) -> IntCC311     fn unsigned_add_overflow_condition(&self) -> IntCC {
312         // TODO: this is what x86 specifies. Is this right for arm64?
313         IntCC::UnsignedLessThan
314     }
315 
316     /// Machine-specific condcode info needed by TargetIsa.
unsigned_sub_overflow_condition(&self) -> IntCC317     fn unsigned_sub_overflow_condition(&self) -> IntCC {
318         // TODO: this is what x86 specifies. Is this right for arm64?
319         IntCC::UnsignedLessThan
320     }
321 }
322