• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1//===-- X86InstrSystem.td - System Instructions ------------*- tablegen -*-===//
2//
3// Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4// See https://llvm.org/LICENSE.txt for license information.
5// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6//
7//===----------------------------------------------------------------------===//
8//
9// This file describes the X86 instructions that are generally used in
10// privileged modes.  These are not typically used by the compiler, but are
11// supported for the assembler and disassembler.
12//
13//===----------------------------------------------------------------------===//
14
15let SchedRW = [WriteSystem] in {
16let Defs = [RAX, RDX] in
17def RDTSC : I<0x31, RawFrm, (outs), (ins), "rdtsc", []>, TB;
18
19let Defs = [RAX, RCX, RDX] in
20def RDTSCP : I<0x01, MRM_F9, (outs), (ins), "rdtscp", []>, TB;
21
22// CPU flow control instructions
23
24let mayLoad = 1, mayStore = 0, hasSideEffects = 1, isTrap = 1 in {
25  def TRAP    : I<0x0B, RawFrm, (outs), (ins), "ud2", [(trap)]>, TB;
26
27  def UD1Wm   : I<0xB9, MRMSrcMem, (outs), (ins GR16:$src1, i16mem:$src2),
28                  "ud1{w} {$src2, $src1|$src1, $src2}", []>, TB, OpSize16;
29  def UD1Lm   : I<0xB9, MRMSrcMem, (outs), (ins GR32:$src1, i32mem:$src2),
30                  "ud1{l} {$src2, $src1|$src1, $src2}", []>, TB, OpSize32;
31  def UD1Qm   : RI<0xB9, MRMSrcMem, (outs), (ins GR64:$src1, i64mem:$src2),
32                   "ud1{q} {$src2, $src1|$src1, $src2}", []>, TB;
33
34  def UD1Wr   : I<0xB9, MRMSrcReg, (outs), (ins GR16:$src1, GR16:$src2),
35                  "ud1{w} {$src2, $src1|$src1, $src2}", []>, TB, OpSize16;
36  def UD1Lr   : I<0xB9, MRMSrcReg, (outs), (ins GR32:$src1, GR32:$src2),
37                  "ud1{l} {$src2, $src1|$src1, $src2}", []>, TB, OpSize32;
38  def UD1Qr   : RI<0xB9, MRMSrcReg, (outs), (ins GR64:$src1, GR64:$src2),
39                   "ud1{q} {$src2, $src1|$src1, $src2}", []>, TB;
40}
41
42def HLT : I<0xF4, RawFrm, (outs), (ins), "hlt", []>;
43def RSM : I<0xAA, RawFrm, (outs), (ins), "rsm", []>, TB;
44
45// Interrupt and SysCall Instructions.
46let Uses = [EFLAGS] in
47  def INTO : I<0xce, RawFrm, (outs), (ins), "into", []>, Requires<[Not64BitMode]>;
48
49def INT3 : I<0xcc, RawFrm, (outs), (ins), "int3", [(int_x86_int (i8 3))]>;
50} // SchedRW
51
52def UBSAN_UD1 : PseudoI<(outs), (ins i32imm:$kind), [(ubsantrap (i32 timm:$kind))]>;
53// The long form of "int $3" turns into int3 as a size optimization.
54// FIXME: This doesn't work because InstAlias can't match immediate constants.
55//def : InstAlias<"int\t$3", (INT3)>;
56
57let SchedRW = [WriteSystem] in {
58
59def INT : Ii8<0xcd, RawFrm, (outs), (ins u8imm:$trap), "int\t$trap",
60              [(int_x86_int timm:$trap)]>;
61
62
63def SYSCALL  : I<0x05, RawFrm, (outs), (ins), "syscall", []>, TB;
64def SYSRET   : I<0x07, RawFrm, (outs), (ins), "sysret{l}", []>, TB;
65def SYSRET64 :RI<0x07, RawFrm, (outs), (ins), "sysretq", []>, TB,
66               Requires<[In64BitMode]>;
67
68def SYSENTER : I<0x34, RawFrm, (outs), (ins), "sysenter", []>, TB;
69
70def SYSEXIT   : I<0x35, RawFrm, (outs), (ins), "sysexit{l}", []>, TB;
71def SYSEXIT64 :RI<0x35, RawFrm, (outs), (ins), "sysexitq", []>, TB,
72                  Requires<[In64BitMode]>;
73} // SchedRW
74
75def : Pat<(debugtrap),
76          (INT3)>, Requires<[NotPS4]>;
77def : Pat<(debugtrap),
78          (INT (i8 0x41))>, Requires<[IsPS4]>;
79
80//===----------------------------------------------------------------------===//
81//  Input/Output Instructions.
82//
83let SchedRW = [WriteSystem] in {
84let Defs = [AL], Uses = [DX] in
85def IN8rr  : I<0xEC, RawFrm, (outs), (ins), "in{b}\t{%dx, %al|al, dx}", []>;
86let Defs = [AX], Uses = [DX] in
87def IN16rr : I<0xED, RawFrm, (outs), (ins), "in{w}\t{%dx, %ax|ax, dx}", []>,
88               OpSize16;
89let Defs = [EAX], Uses = [DX] in
90def IN32rr : I<0xED, RawFrm, (outs), (ins), "in{l}\t{%dx, %eax|eax, dx}", []>,
91               OpSize32;
92
93let Defs = [AL] in
94def IN8ri  : Ii8<0xE4, RawFrm, (outs), (ins u8imm:$port),
95                 "in{b}\t{$port, %al|al, $port}", []>;
96let Defs = [AX] in
97def IN16ri : Ii8<0xE5, RawFrm, (outs), (ins u8imm:$port),
98                 "in{w}\t{$port, %ax|ax, $port}", []>, OpSize16;
99let Defs = [EAX] in
100def IN32ri : Ii8<0xE5, RawFrm, (outs), (ins u8imm:$port),
101                 "in{l}\t{$port, %eax|eax, $port}", []>, OpSize32;
102
103let Uses = [DX, AL] in
104def OUT8rr  : I<0xEE, RawFrm, (outs), (ins), "out{b}\t{%al, %dx|dx, al}", []>;
105let Uses = [DX, AX] in
106def OUT16rr : I<0xEF, RawFrm, (outs), (ins), "out{w}\t{%ax, %dx|dx, ax}", []>,
107                OpSize16;
108let Uses = [DX, EAX] in
109def OUT32rr : I<0xEF, RawFrm, (outs), (ins), "out{l}\t{%eax, %dx|dx, eax}", []>,
110                OpSize32;
111
112let Uses = [AL] in
113def OUT8ir  : Ii8<0xE6, RawFrm, (outs), (ins u8imm:$port),
114                   "out{b}\t{%al, $port|$port, al}", []>;
115let Uses = [AX] in
116def OUT16ir : Ii8<0xE7, RawFrm, (outs), (ins u8imm:$port),
117                   "out{w}\t{%ax, $port|$port, ax}", []>, OpSize16;
118let Uses = [EAX] in
119def OUT32ir : Ii8<0xE7, RawFrm, (outs), (ins u8imm:$port),
120                  "out{l}\t{%eax, $port|$port, eax}", []>, OpSize32;
121
122} // SchedRW
123
124//===----------------------------------------------------------------------===//
125// Moves to and from debug registers
126
127let SchedRW = [WriteSystem] in {
128def MOV32rd : I<0x21, MRMDestReg, (outs GR32:$dst), (ins DEBUG_REG:$src),
129                "mov{l}\t{$src, $dst|$dst, $src}", []>, TB,
130                Requires<[Not64BitMode]>;
131def MOV64rd : I<0x21, MRMDestReg, (outs GR64:$dst), (ins DEBUG_REG:$src),
132                "mov{q}\t{$src, $dst|$dst, $src}", []>, TB,
133                Requires<[In64BitMode]>;
134
135def MOV32dr : I<0x23, MRMSrcReg, (outs DEBUG_REG:$dst), (ins GR32:$src),
136                "mov{l}\t{$src, $dst|$dst, $src}", []>, TB,
137                Requires<[Not64BitMode]>;
138def MOV64dr : I<0x23, MRMSrcReg, (outs DEBUG_REG:$dst), (ins GR64:$src),
139                "mov{q}\t{$src, $dst|$dst, $src}", []>, TB,
140                Requires<[In64BitMode]>;
141} // SchedRW
142
143//===----------------------------------------------------------------------===//
144// Moves to and from control registers
145
146let SchedRW = [WriteSystem] in {
147def MOV32rc : I<0x20, MRMDestReg, (outs GR32:$dst), (ins CONTROL_REG:$src),
148                "mov{l}\t{$src, $dst|$dst, $src}", []>, TB,
149                Requires<[Not64BitMode]>;
150def MOV64rc : I<0x20, MRMDestReg, (outs GR64:$dst), (ins CONTROL_REG:$src),
151                "mov{q}\t{$src, $dst|$dst, $src}", []>, TB,
152                Requires<[In64BitMode]>;
153
154def MOV32cr : I<0x22, MRMSrcReg, (outs CONTROL_REG:$dst), (ins GR32:$src),
155                "mov{l}\t{$src, $dst|$dst, $src}", []>, TB,
156                Requires<[Not64BitMode]>;
157def MOV64cr : I<0x22, MRMSrcReg, (outs CONTROL_REG:$dst), (ins GR64:$src),
158                "mov{q}\t{$src, $dst|$dst, $src}", []>, TB,
159                Requires<[In64BitMode]>;
160} // SchedRW
161
162//===----------------------------------------------------------------------===//
163// Segment override instruction prefixes
164
165let SchedRW = [WriteNop] in {
166def CS_PREFIX : I<0x2E, PrefixByte, (outs), (ins), "cs", []>;
167def SS_PREFIX : I<0x36, PrefixByte, (outs), (ins), "ss", []>;
168def DS_PREFIX : I<0x3E, PrefixByte, (outs), (ins), "ds", []>;
169def ES_PREFIX : I<0x26, PrefixByte, (outs), (ins), "es", []>;
170def FS_PREFIX : I<0x64, PrefixByte, (outs), (ins), "fs", []>;
171def GS_PREFIX : I<0x65, PrefixByte, (outs), (ins), "gs", []>;
172} // SchedRW
173
174//===----------------------------------------------------------------------===//
175// Moves to and from segment registers.
176//
177
178let SchedRW = [WriteMove] in {
179def MOV16rs : I<0x8C, MRMDestReg, (outs GR16:$dst), (ins SEGMENT_REG:$src),
180                "mov{w}\t{$src, $dst|$dst, $src}", []>, OpSize16;
181def MOV32rs : I<0x8C, MRMDestReg, (outs GR32:$dst), (ins SEGMENT_REG:$src),
182                "mov{l}\t{$src, $dst|$dst, $src}", []>, OpSize32;
183def MOV64rs : RI<0x8C, MRMDestReg, (outs GR64:$dst), (ins SEGMENT_REG:$src),
184                 "mov{q}\t{$src, $dst|$dst, $src}", []>;
185let mayStore = 1 in {
186def MOV16ms : I<0x8C, MRMDestMem, (outs), (ins i16mem:$dst, SEGMENT_REG:$src),
187                "mov{w}\t{$src, $dst|$dst, $src}", []>;
188}
189def MOV16sr : I<0x8E, MRMSrcReg, (outs SEGMENT_REG:$dst), (ins GR16:$src),
190                "mov{w}\t{$src, $dst|$dst, $src}", []>, OpSize16;
191def MOV32sr : I<0x8E, MRMSrcReg, (outs SEGMENT_REG:$dst), (ins GR32:$src),
192                "mov{l}\t{$src, $dst|$dst, $src}", []>, OpSize32;
193def MOV64sr : RI<0x8E, MRMSrcReg, (outs SEGMENT_REG:$dst), (ins GR64:$src),
194                 "mov{q}\t{$src, $dst|$dst, $src}", []>;
195let mayLoad = 1 in {
196def MOV16sm : I<0x8E, MRMSrcMem, (outs SEGMENT_REG:$dst), (ins i16mem:$src),
197                "mov{w}\t{$src, $dst|$dst, $src}", []>;
198}
199} // SchedRW
200
201//===----------------------------------------------------------------------===//
202// Segmentation support instructions.
203
204let SchedRW = [WriteSystem] in {
205def SWAPGS : I<0x01, MRM_F8, (outs), (ins), "swapgs", []>, TB;
206
207let mayLoad = 1 in
208def LAR16rm : I<0x02, MRMSrcMem, (outs GR16:$dst), (ins i16mem:$src),
209                "lar{w}\t{$src, $dst|$dst, $src}", []>, TB,
210                OpSize16, NotMemoryFoldable;
211def LAR16rr : I<0x02, MRMSrcReg, (outs GR16:$dst), (ins GR16orGR32orGR64:$src),
212                "lar{w}\t{$src, $dst|$dst, $src}", []>, TB,
213                OpSize16, NotMemoryFoldable;
214
215let mayLoad = 1 in
216def LAR32rm : I<0x02, MRMSrcMem, (outs GR32:$dst), (ins i16mem:$src),
217                "lar{l}\t{$src, $dst|$dst, $src}", []>, TB,
218                OpSize32, NotMemoryFoldable;
219def LAR32rr : I<0x02, MRMSrcReg, (outs GR32:$dst), (ins GR16orGR32orGR64:$src),
220                "lar{l}\t{$src, $dst|$dst, $src}", []>, TB,
221                OpSize32, NotMemoryFoldable;
222let mayLoad = 1 in
223def LAR64rm : RI<0x02, MRMSrcMem, (outs GR64:$dst), (ins i16mem:$src),
224                 "lar{q}\t{$src, $dst|$dst, $src}", []>, TB, NotMemoryFoldable;
225def LAR64rr : RI<0x02, MRMSrcReg, (outs GR64:$dst), (ins GR16orGR32orGR64:$src),
226                 "lar{q}\t{$src, $dst|$dst, $src}", []>, TB, NotMemoryFoldable;
227
228let mayLoad = 1 in
229def LSL16rm : I<0x03, MRMSrcMem, (outs GR16:$dst), (ins i16mem:$src),
230                "lsl{w}\t{$src, $dst|$dst, $src}", []>, TB,
231                OpSize16, NotMemoryFoldable;
232def LSL16rr : I<0x03, MRMSrcReg, (outs GR16:$dst), (ins GR16orGR32orGR64:$src),
233                "lsl{w}\t{$src, $dst|$dst, $src}", []>, TB,
234                OpSize16, NotMemoryFoldable;
235let mayLoad = 1 in
236def LSL32rm : I<0x03, MRMSrcMem, (outs GR32:$dst), (ins i16mem:$src),
237                "lsl{l}\t{$src, $dst|$dst, $src}", []>, TB,
238                OpSize32, NotMemoryFoldable;
239def LSL32rr : I<0x03, MRMSrcReg, (outs GR32:$dst), (ins GR16orGR32orGR64:$src),
240                "lsl{l}\t{$src, $dst|$dst, $src}", []>, TB,
241                OpSize32, NotMemoryFoldable;
242let mayLoad = 1 in
243def LSL64rm : RI<0x03, MRMSrcMem, (outs GR64:$dst), (ins i16mem:$src),
244                 "lsl{q}\t{$src, $dst|$dst, $src}", []>, TB, NotMemoryFoldable;
245def LSL64rr : RI<0x03, MRMSrcReg, (outs GR64:$dst), (ins GR16orGR32orGR64:$src),
246                 "lsl{q}\t{$src, $dst|$dst, $src}", []>, TB, NotMemoryFoldable;
247
248def INVLPG : I<0x01, MRM7m, (outs), (ins i8mem:$addr), "invlpg\t$addr", []>, TB;
249
250def STR16r : I<0x00, MRM1r, (outs GR16:$dst), (ins),
251               "str{w}\t$dst", []>, TB, OpSize16;
252def STR32r : I<0x00, MRM1r, (outs GR32:$dst), (ins),
253               "str{l}\t$dst", []>, TB, OpSize32;
254def STR64r : RI<0x00, MRM1r, (outs GR64:$dst), (ins),
255                "str{q}\t$dst", []>, TB;
256let mayStore = 1 in
257def STRm   : I<0x00, MRM1m, (outs), (ins i16mem:$dst), "str{w}\t$dst", []>, TB;
258
259def LTRr : I<0x00, MRM3r, (outs), (ins GR16:$src), "ltr{w}\t$src", []>, TB, NotMemoryFoldable;
260let mayLoad = 1 in
261def LTRm : I<0x00, MRM3m, (outs), (ins i16mem:$src), "ltr{w}\t$src", []>, TB, NotMemoryFoldable;
262
263def PUSHCS16 : I<0x0E, RawFrm, (outs), (ins), "push{w}\t{%cs|cs}", []>,
264                 OpSize16, Requires<[Not64BitMode]>;
265def PUSHCS32 : I<0x0E, RawFrm, (outs), (ins), "push{l}\t{%cs|cs}", []>,
266                 OpSize32, Requires<[Not64BitMode]>;
267def PUSHSS16 : I<0x16, RawFrm, (outs), (ins), "push{w}\t{%ss|ss}", []>,
268                 OpSize16, Requires<[Not64BitMode]>;
269def PUSHSS32 : I<0x16, RawFrm, (outs), (ins), "push{l}\t{%ss|ss}", []>,
270                 OpSize32, Requires<[Not64BitMode]>;
271def PUSHDS16 : I<0x1E, RawFrm, (outs), (ins), "push{w}\t{%ds|ds}", []>,
272                 OpSize16, Requires<[Not64BitMode]>;
273def PUSHDS32 : I<0x1E, RawFrm, (outs), (ins), "push{l}\t{%ds|ds}", []>,
274                 OpSize32, Requires<[Not64BitMode]>;
275def PUSHES16 : I<0x06, RawFrm, (outs), (ins), "push{w}\t{%es|es}", []>,
276                 OpSize16, Requires<[Not64BitMode]>;
277def PUSHES32 : I<0x06, RawFrm, (outs), (ins), "push{l}\t{%es|es}", []>,
278                 OpSize32, Requires<[Not64BitMode]>;
279def PUSHFS16 : I<0xa0, RawFrm, (outs), (ins), "push{w}\t{%fs|fs}", []>,
280                 OpSize16, TB;
281def PUSHFS32 : I<0xa0, RawFrm, (outs), (ins), "push{l}\t{%fs|fs}", []>, TB,
282                 OpSize32, Requires<[Not64BitMode]>;
283def PUSHGS16 : I<0xa8, RawFrm, (outs), (ins), "push{w}\t{%gs|gs}", []>,
284                 OpSize16, TB;
285def PUSHGS32 : I<0xa8, RawFrm, (outs), (ins), "push{l}\t{%gs|gs}", []>, TB,
286                 OpSize32, Requires<[Not64BitMode]>;
287def PUSHFS64 : I<0xa0, RawFrm, (outs), (ins), "push{q}\t{%fs|fs}", []>, TB,
288                 OpSize32, Requires<[In64BitMode]>;
289def PUSHGS64 : I<0xa8, RawFrm, (outs), (ins), "push{q}\t{%gs|gs}", []>, TB,
290                 OpSize32, Requires<[In64BitMode]>;
291
292// No "pop cs" instruction.
293def POPSS16 : I<0x17, RawFrm, (outs), (ins), "pop{w}\t{%ss|ss}", []>,
294              OpSize16, Requires<[Not64BitMode]>;
295def POPSS32 : I<0x17, RawFrm, (outs), (ins), "pop{l}\t{%ss|ss}", []>,
296              OpSize32, Requires<[Not64BitMode]>;
297
298def POPDS16 : I<0x1F, RawFrm, (outs), (ins), "pop{w}\t{%ds|ds}", []>,
299              OpSize16, Requires<[Not64BitMode]>;
300def POPDS32 : I<0x1F, RawFrm, (outs), (ins), "pop{l}\t{%ds|ds}", []>,
301              OpSize32, Requires<[Not64BitMode]>;
302
303def POPES16 : I<0x07, RawFrm, (outs), (ins), "pop{w}\t{%es|es}", []>,
304              OpSize16, Requires<[Not64BitMode]>;
305def POPES32 : I<0x07, RawFrm, (outs), (ins), "pop{l}\t{%es|es}", []>,
306              OpSize32, Requires<[Not64BitMode]>;
307
308def POPFS16 : I<0xa1, RawFrm, (outs), (ins), "pop{w}\t{%fs|fs}", []>,
309                OpSize16, TB;
310def POPFS32 : I<0xa1, RawFrm, (outs), (ins), "pop{l}\t{%fs|fs}", []>, TB,
311                OpSize32, Requires<[Not64BitMode]>;
312def POPFS64 : I<0xa1, RawFrm, (outs), (ins), "pop{q}\t{%fs|fs}", []>, TB,
313                OpSize32, Requires<[In64BitMode]>;
314
315def POPGS16 : I<0xa9, RawFrm, (outs), (ins), "pop{w}\t{%gs|gs}", []>,
316                OpSize16, TB;
317def POPGS32 : I<0xa9, RawFrm, (outs), (ins), "pop{l}\t{%gs|gs}", []>, TB,
318                OpSize32, Requires<[Not64BitMode]>;
319def POPGS64 : I<0xa9, RawFrm, (outs), (ins), "pop{q}\t{%gs|gs}", []>, TB,
320                OpSize32, Requires<[In64BitMode]>;
321
322def LDS16rm : I<0xc5, MRMSrcMem, (outs GR16:$dst), (ins opaquemem:$src),
323                "lds{w}\t{$src, $dst|$dst, $src}", []>, OpSize16,
324                Requires<[Not64BitMode]>;
325def LDS32rm : I<0xc5, MRMSrcMem, (outs GR32:$dst), (ins opaquemem:$src),
326                "lds{l}\t{$src, $dst|$dst, $src}", []>, OpSize32,
327                Requires<[Not64BitMode]>;
328
329def LSS16rm : I<0xb2, MRMSrcMem, (outs GR16:$dst), (ins opaquemem:$src),
330                "lss{w}\t{$src, $dst|$dst, $src}", []>, TB, OpSize16;
331def LSS32rm : I<0xb2, MRMSrcMem, (outs GR32:$dst), (ins opaquemem:$src),
332                "lss{l}\t{$src, $dst|$dst, $src}", []>, TB, OpSize32;
333def LSS64rm : RI<0xb2, MRMSrcMem, (outs GR64:$dst), (ins opaquemem:$src),
334                 "lss{q}\t{$src, $dst|$dst, $src}", []>, TB;
335
336def LES16rm : I<0xc4, MRMSrcMem, (outs GR16:$dst), (ins opaquemem:$src),
337                "les{w}\t{$src, $dst|$dst, $src}", []>, OpSize16,
338                Requires<[Not64BitMode]>;
339def LES32rm : I<0xc4, MRMSrcMem, (outs GR32:$dst), (ins opaquemem:$src),
340                "les{l}\t{$src, $dst|$dst, $src}", []>, OpSize32,
341                Requires<[Not64BitMode]>;
342
343def LFS16rm : I<0xb4, MRMSrcMem, (outs GR16:$dst), (ins opaquemem:$src),
344                "lfs{w}\t{$src, $dst|$dst, $src}", []>, TB, OpSize16;
345def LFS32rm : I<0xb4, MRMSrcMem, (outs GR32:$dst), (ins opaquemem:$src),
346                "lfs{l}\t{$src, $dst|$dst, $src}", []>, TB, OpSize32;
347def LFS64rm : RI<0xb4, MRMSrcMem, (outs GR64:$dst), (ins opaquemem:$src),
348                 "lfs{q}\t{$src, $dst|$dst, $src}", []>, TB;
349
350def LGS16rm : I<0xb5, MRMSrcMem, (outs GR16:$dst), (ins opaquemem:$src),
351                "lgs{w}\t{$src, $dst|$dst, $src}", []>, TB, OpSize16;
352def LGS32rm : I<0xb5, MRMSrcMem, (outs GR32:$dst), (ins opaquemem:$src),
353                "lgs{l}\t{$src, $dst|$dst, $src}", []>, TB, OpSize32;
354
355def LGS64rm : RI<0xb5, MRMSrcMem, (outs GR64:$dst), (ins opaquemem:$src),
356                 "lgs{q}\t{$src, $dst|$dst, $src}", []>, TB;
357
358def VERRr : I<0x00, MRM4r, (outs), (ins GR16:$seg), "verr\t$seg", []>, TB, NotMemoryFoldable;
359def VERWr : I<0x00, MRM5r, (outs), (ins GR16:$seg), "verw\t$seg", []>, TB, NotMemoryFoldable;
360let mayLoad = 1 in {
361def VERRm : I<0x00, MRM4m, (outs), (ins i16mem:$seg), "verr\t$seg", []>, TB, NotMemoryFoldable;
362def VERWm : I<0x00, MRM5m, (outs), (ins i16mem:$seg), "verw\t$seg", []>, TB, NotMemoryFoldable;
363}
364} // SchedRW
365
366//===----------------------------------------------------------------------===//
367// Descriptor-table support instructions
368
369let SchedRW = [WriteSystem] in {
370def SGDT16m : I<0x01, MRM0m, (outs), (ins opaquemem:$dst),
371                "sgdtw\t$dst", []>, TB, OpSize16, Requires<[Not64BitMode]>;
372def SGDT32m : I<0x01, MRM0m, (outs), (ins opaquemem:$dst),
373                "sgdt{l|d}\t$dst", []>, OpSize32, TB, Requires <[Not64BitMode]>;
374def SGDT64m : I<0x01, MRM0m, (outs), (ins opaquemem:$dst),
375                "sgdt{q}\t$dst", []>, TB, Requires <[In64BitMode]>;
376def SIDT16m : I<0x01, MRM1m, (outs), (ins opaquemem:$dst),
377                "sidtw\t$dst", []>, TB, OpSize16, Requires<[Not64BitMode]>;
378def SIDT32m : I<0x01, MRM1m, (outs), (ins opaquemem:$dst),
379                "sidt{l|d}\t$dst", []>, OpSize32, TB, Requires <[Not64BitMode]>;
380def SIDT64m : I<0x01, MRM1m, (outs), (ins opaquemem:$dst),
381                "sidt{q}\t$dst", []>, TB, Requires <[In64BitMode]>;
382def SLDT16r : I<0x00, MRM0r, (outs GR16:$dst), (ins),
383                "sldt{w}\t$dst", []>, TB, OpSize16;
384let mayStore = 1 in
385def SLDT16m : I<0x00, MRM0m, (outs), (ins i16mem:$dst),
386                "sldt{w}\t$dst", []>, TB;
387def SLDT32r : I<0x00, MRM0r, (outs GR32:$dst), (ins),
388                "sldt{l}\t$dst", []>, OpSize32, TB;
389
390// LLDT is not interpreted specially in 64-bit mode because there is no sign
391//   extension.
392def SLDT64r : RI<0x00, MRM0r, (outs GR64:$dst), (ins),
393                 "sldt{q}\t$dst", []>, TB, Requires<[In64BitMode]>;
394
395def LGDT16m : I<0x01, MRM2m, (outs), (ins opaquemem:$src),
396                "lgdtw\t$src", []>, TB, OpSize16, Requires<[Not64BitMode]>;
397def LGDT32m : I<0x01, MRM2m, (outs), (ins opaquemem:$src),
398                "lgdt{l|d}\t$src", []>, OpSize32, TB, Requires<[Not64BitMode]>;
399def LGDT64m : I<0x01, MRM2m, (outs), (ins opaquemem:$src),
400                "lgdt{q}\t$src", []>, TB, Requires<[In64BitMode]>;
401def LIDT16m : I<0x01, MRM3m, (outs), (ins opaquemem:$src),
402                "lidtw\t$src", []>, TB, OpSize16, Requires<[Not64BitMode]>;
403def LIDT32m : I<0x01, MRM3m, (outs), (ins opaquemem:$src),
404                "lidt{l|d}\t$src", []>, OpSize32, TB, Requires<[Not64BitMode]>;
405def LIDT64m : I<0x01, MRM3m, (outs), (ins opaquemem:$src),
406                "lidt{q}\t$src", []>, TB, Requires<[In64BitMode]>;
407def LLDT16r : I<0x00, MRM2r, (outs), (ins GR16:$src),
408                "lldt{w}\t$src", []>, TB, NotMemoryFoldable;
409let mayLoad = 1 in
410def LLDT16m : I<0x00, MRM2m, (outs), (ins i16mem:$src),
411                "lldt{w}\t$src", []>, TB, NotMemoryFoldable;
412} // SchedRW
413
414//===----------------------------------------------------------------------===//
415// Specialized register support
416let SchedRW = [WriteSystem] in {
417let Uses = [EAX, ECX, EDX] in
418def WRMSR : I<0x30, RawFrm, (outs), (ins), "wrmsr", []>, TB;
419let Defs = [EAX, EDX], Uses = [ECX] in
420def RDMSR : I<0x32, RawFrm, (outs), (ins), "rdmsr", []>, TB;
421
422let Defs = [RAX, RDX], Uses = [ECX] in
423def RDPMC : I<0x33, RawFrm, (outs), (ins), "rdpmc", []>, TB;
424
425def SMSW16r : I<0x01, MRM4r, (outs GR16:$dst), (ins),
426                "smsw{w}\t$dst", []>, OpSize16, TB;
427def SMSW32r : I<0x01, MRM4r, (outs GR32:$dst), (ins),
428                "smsw{l}\t$dst", []>, OpSize32, TB;
429// no m form encodable; use SMSW16m
430def SMSW64r : RI<0x01, MRM4r, (outs GR64:$dst), (ins),
431                 "smsw{q}\t$dst", []>, TB;
432
433// For memory operands, there is only a 16-bit form
434def SMSW16m : I<0x01, MRM4m, (outs), (ins i16mem:$dst),
435                "smsw{w}\t$dst", []>, TB;
436
437def LMSW16r : I<0x01, MRM6r, (outs), (ins GR16:$src),
438                "lmsw{w}\t$src", []>, TB, NotMemoryFoldable;
439let mayLoad = 1 in
440def LMSW16m : I<0x01, MRM6m, (outs), (ins i16mem:$src),
441                "lmsw{w}\t$src", []>, TB, NotMemoryFoldable;
442
443let Defs = [EAX, EBX, ECX, EDX], Uses = [EAX, ECX] in
444  def CPUID : I<0xA2, RawFrm, (outs), (ins), "cpuid", []>, TB;
445} // SchedRW
446
447//===----------------------------------------------------------------------===//
448// Cache instructions
449let SchedRW = [WriteSystem] in {
450def INVD : I<0x08, RawFrm, (outs), (ins), "invd", []>, TB;
451def WBINVD : I<0x09, RawFrm, (outs), (ins), "wbinvd", [(int_x86_wbinvd)]>, PS;
452
453// wbnoinvd is like wbinvd, except without invalidation
454// encoding: like wbinvd + an 0xF3 prefix
455def WBNOINVD : I<0x09, RawFrm, (outs), (ins), "wbnoinvd",
456                 [(int_x86_wbnoinvd)]>, XS,
457                 Requires<[HasWBNOINVD]>;
458} // SchedRW
459
460//===----------------------------------------------------------------------===//
461// CET instructions
462// Use with caution, availability is not predicated on features.
463let SchedRW = [WriteSystem] in {
464  let Uses = [SSP] in {
465    let Defs = [SSP] in {
466      def INCSSPD : I<0xAE, MRM5r, (outs), (ins GR32:$src), "incsspd\t$src",
467                       [(int_x86_incsspd GR32:$src)]>, XS;
468      def INCSSPQ : RI<0xAE, MRM5r, (outs), (ins GR64:$src), "incsspq\t$src",
469                       [(int_x86_incsspq GR64:$src)]>, XS;
470    } // Defs SSP
471
472    let Constraints = "$src = $dst" in {
473      def RDSSPD : I<0x1E, MRM1r, (outs GR32:$dst), (ins GR32:$src),
474                     "rdsspd\t$dst",
475                     [(set GR32:$dst, (int_x86_rdsspd GR32:$src))]>, XS;
476      def RDSSPQ : RI<0x1E, MRM1r, (outs GR64:$dst), (ins GR64:$src),
477                     "rdsspq\t$dst",
478                     [(set GR64:$dst, (int_x86_rdsspq GR64:$src))]>, XS;
479    }
480
481    let Defs = [SSP] in {
482      def SAVEPREVSSP : I<0x01, MRM_EA, (outs), (ins), "saveprevssp",
483                       [(int_x86_saveprevssp)]>, XS;
484      def RSTORSSP : I<0x01, MRM5m, (outs), (ins i32mem:$src),
485                       "rstorssp\t$src",
486                       [(int_x86_rstorssp addr:$src)]>, XS;
487    } // Defs SSP
488  } // Uses SSP
489
490  def WRSSD : I<0xF6, MRMDestMem, (outs), (ins i32mem:$dst, GR32:$src),
491                "wrssd\t{$src, $dst|$dst, $src}",
492                [(int_x86_wrssd GR32:$src, addr:$dst)]>, T8PS;
493  def WRSSQ : RI<0xF6, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
494                 "wrssq\t{$src, $dst|$dst, $src}",
495                 [(int_x86_wrssq GR64:$src, addr:$dst)]>, T8PS;
496  def WRUSSD : I<0xF5, MRMDestMem, (outs), (ins i32mem:$dst, GR32:$src),
497                 "wrussd\t{$src, $dst|$dst, $src}",
498                 [(int_x86_wrussd GR32:$src, addr:$dst)]>, T8PD;
499  def WRUSSQ : RI<0xF5, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
500                  "wrussq\t{$src, $dst|$dst, $src}",
501                  [(int_x86_wrussq GR64:$src, addr:$dst)]>, T8PD;
502
503  let Defs = [SSP] in {
504    let Uses = [SSP] in {
505        def SETSSBSY : I<0x01, MRM_E8, (outs), (ins), "setssbsy",
506                         [(int_x86_setssbsy)]>, XS;
507    } // Uses SSP
508
509    def CLRSSBSY : I<0xAE, MRM6m, (outs), (ins i32mem:$src),
510                     "clrssbsy\t$src",
511                     [(int_x86_clrssbsy addr:$src)]>, XS;
512  } // Defs SSP
513} // SchedRW
514
515let SchedRW = [WriteSystem] in {
516    def ENDBR64 : I<0x1E, MRM_FA, (outs), (ins), "endbr64", []>, XS;
517    def ENDBR32 : I<0x1E, MRM_FB, (outs), (ins), "endbr32", []>, XS;
518} // SchedRW
519
520//===----------------------------------------------------------------------===//
521// XSAVE instructions
522let SchedRW = [WriteSystem] in {
523let Predicates = [HasXSAVE] in {
524let Defs = [EDX, EAX], Uses = [ECX] in
525  def XGETBV : I<0x01, MRM_D0, (outs), (ins), "xgetbv", []>, PS;
526
527let Uses = [EDX, EAX, ECX] in
528  def XSETBV : I<0x01, MRM_D1, (outs), (ins),
529                "xsetbv",
530                [(int_x86_xsetbv ECX, EDX, EAX)]>, PS;
531
532} // HasXSAVE
533
534let Uses = [EDX, EAX] in {
535def XSAVE : I<0xAE, MRM4m, (outs), (ins opaquemem:$dst),
536              "xsave\t$dst",
537              [(int_x86_xsave addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVE]>;
538def XSAVE64 : RI<0xAE, MRM4m, (outs), (ins opaquemem:$dst),
539                 "xsave64\t$dst",
540                 [(int_x86_xsave64 addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVE, In64BitMode]>;
541def XRSTOR : I<0xAE, MRM5m, (outs), (ins opaquemem:$dst),
542               "xrstor\t$dst",
543               [(int_x86_xrstor addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVE]>;
544def XRSTOR64 : RI<0xAE, MRM5m, (outs), (ins opaquemem:$dst),
545                  "xrstor64\t$dst",
546                  [(int_x86_xrstor64 addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVE, In64BitMode]>;
547def XSAVEOPT : I<0xAE, MRM6m, (outs), (ins opaquemem:$dst),
548                 "xsaveopt\t$dst",
549                 [(int_x86_xsaveopt addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVEOPT]>;
550def XSAVEOPT64 : RI<0xAE, MRM6m, (outs), (ins opaquemem:$dst),
551                    "xsaveopt64\t$dst",
552                    [(int_x86_xsaveopt64 addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVEOPT, In64BitMode]>;
553def XSAVEC : I<0xC7, MRM4m, (outs), (ins opaquemem:$dst),
554               "xsavec\t$dst",
555               [(int_x86_xsavec addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVEC]>;
556def XSAVEC64 : RI<0xC7, MRM4m, (outs), (ins opaquemem:$dst),
557                 "xsavec64\t$dst",
558                 [(int_x86_xsavec64 addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVEC, In64BitMode]>;
559def XSAVES : I<0xC7, MRM5m, (outs), (ins opaquemem:$dst),
560               "xsaves\t$dst",
561               [(int_x86_xsaves addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVES]>;
562def XSAVES64 : RI<0xC7, MRM5m, (outs), (ins opaquemem:$dst),
563                  "xsaves64\t$dst",
564                  [(int_x86_xsaves64 addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVE, In64BitMode]>;
565def XRSTORS : I<0xC7, MRM3m, (outs), (ins opaquemem:$dst),
566                "xrstors\t$dst",
567                [(int_x86_xrstors addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVES]>;
568def XRSTORS64 : RI<0xC7, MRM3m, (outs), (ins opaquemem:$dst),
569                   "xrstors64\t$dst",
570                   [(int_x86_xrstors64 addr:$dst, EDX, EAX)]>, PS, Requires<[HasXSAVES, In64BitMode]>;
571} // Uses
572} // SchedRW
573
574//===----------------------------------------------------------------------===//
575// VIA PadLock crypto instructions
576let Defs = [RAX, RDI], Uses = [RDX, RDI], SchedRW = [WriteSystem] in
577  def XSTORE : I<0xa7, MRM_C0, (outs), (ins), "xstore", []>, TB, REP;
578
579def : InstAlias<"xstorerng", (XSTORE)>;
580
581let SchedRW = [WriteSystem] in {
582let Defs = [RSI, RDI], Uses = [RBX, RDX, RSI, RDI] in {
583  def XCRYPTECB : I<0xa7, MRM_C8, (outs), (ins), "xcryptecb", []>, TB, REP;
584  def XCRYPTCBC : I<0xa7, MRM_D0, (outs), (ins), "xcryptcbc", []>, TB, REP;
585  def XCRYPTCTR : I<0xa7, MRM_D8, (outs), (ins), "xcryptctr", []>, TB, REP;
586  def XCRYPTCFB : I<0xa7, MRM_E0, (outs), (ins), "xcryptcfb", []>, TB, REP;
587  def XCRYPTOFB : I<0xa7, MRM_E8, (outs), (ins), "xcryptofb", []>, TB, REP;
588}
589
590let Defs = [RAX, RSI, RDI], Uses = [RAX, RSI, RDI] in {
591  def XSHA1 : I<0xa6, MRM_C8, (outs), (ins), "xsha1", []>, TB, REP;
592  def XSHA256 : I<0xa6, MRM_D0, (outs), (ins), "xsha256", []>, TB, REP;
593}
594let Defs = [RAX, RDX, RSI], Uses = [RAX, RSI] in
595  def MONTMUL : I<0xa6, MRM_C0, (outs), (ins), "montmul", []>, TB, REP;
596} // SchedRW
597
598//==-----------------------------------------------------------------------===//
599// PKU  - enable protection key
600let SchedRW = [WriteSystem] in {
601let Defs = [EAX, EDX], Uses = [ECX] in
602  def RDPKRUr : I<0x01, MRM_EE, (outs), (ins), "rdpkru",
603                  [(set EAX, (X86rdpkru ECX)), (implicit EDX)]>, PS;
604let Uses = [EAX, ECX, EDX] in
605  def WRPKRUr : I<0x01, MRM_EF, (outs), (ins), "wrpkru",
606                  [(X86wrpkru EAX, EDX, ECX)]>, PS;
607} // SchedRW
608
609//===----------------------------------------------------------------------===//
610// FS/GS Base Instructions
611let Predicates = [HasFSGSBase, In64BitMode], SchedRW = [WriteSystem] in {
612  def RDFSBASE : I<0xAE, MRM0r, (outs GR32:$dst), (ins),
613                   "rdfsbase{l}\t$dst",
614                   [(set GR32:$dst, (int_x86_rdfsbase_32))]>, XS;
615  def RDFSBASE64 : RI<0xAE, MRM0r, (outs GR64:$dst), (ins),
616                     "rdfsbase{q}\t$dst",
617                     [(set GR64:$dst, (int_x86_rdfsbase_64))]>, XS;
618  def RDGSBASE : I<0xAE, MRM1r, (outs GR32:$dst), (ins),
619                   "rdgsbase{l}\t$dst",
620                   [(set GR32:$dst, (int_x86_rdgsbase_32))]>, XS;
621  def RDGSBASE64 : RI<0xAE, MRM1r, (outs GR64:$dst), (ins),
622                     "rdgsbase{q}\t$dst",
623                     [(set GR64:$dst, (int_x86_rdgsbase_64))]>, XS;
624  def WRFSBASE : I<0xAE, MRM2r, (outs), (ins GR32:$src),
625                   "wrfsbase{l}\t$src",
626                   [(int_x86_wrfsbase_32 GR32:$src)]>, XS;
627  def WRFSBASE64 : RI<0xAE, MRM2r, (outs), (ins GR64:$src),
628                      "wrfsbase{q}\t$src",
629                      [(int_x86_wrfsbase_64 GR64:$src)]>, XS;
630  def WRGSBASE : I<0xAE, MRM3r, (outs), (ins GR32:$src),
631                   "wrgsbase{l}\t$src",
632                   [(int_x86_wrgsbase_32 GR32:$src)]>, XS;
633  def WRGSBASE64 : RI<0xAE, MRM3r, (outs), (ins GR64:$src),
634                      "wrgsbase{q}\t$src",
635                      [(int_x86_wrgsbase_64 GR64:$src)]>, XS;
636}
637
638//===----------------------------------------------------------------------===//
639// INVPCID Instruction
640let SchedRW = [WriteSystem] in {
641def INVPCID32 : I<0x82, MRMSrcMem, (outs), (ins GR32:$src1, i128mem:$src2),
642                  "invpcid\t{$src2, $src1|$src1, $src2}",
643                  [(int_x86_invpcid GR32:$src1, addr:$src2)]>, T8PD,
644                  Requires<[Not64BitMode, HasINVPCID]>;
645def INVPCID64 : I<0x82, MRMSrcMem, (outs), (ins GR64:$src1, i128mem:$src2),
646                  "invpcid\t{$src2, $src1|$src1, $src2}", []>, T8PD,
647                  Requires<[In64BitMode, HasINVPCID]>;
648} // SchedRW
649
650let Predicates = [In64BitMode, HasINVPCID] in {
651  // The instruction can only use a 64 bit register as the register argument
652  // in 64 bit mode, while the intrinsic only accepts a 32 bit argument
653  // corresponding to it.
654  // The accepted values for now are 0,1,2,3 anyways (see Intel SDM -- INVCPID
655  // type),/ so it doesn't hurt us that one can't supply a 64 bit value here.
656  def : Pat<(int_x86_invpcid GR32:$src1, addr:$src2),
657            (INVPCID64
658              (SUBREG_TO_REG (i64 0), (MOV32rr GR32:$src1), sub_32bit),
659              addr:$src2)>;
660}
661
662
663//===----------------------------------------------------------------------===//
664// SMAP Instruction
665let Defs = [EFLAGS], SchedRW = [WriteSystem] in {
666  def CLAC : I<0x01, MRM_CA, (outs), (ins), "clac", []>, PS;
667  def STAC : I<0x01, MRM_CB, (outs), (ins), "stac", []>, PS;
668}
669
670//===----------------------------------------------------------------------===//
671// SMX Instruction
672let SchedRW = [WriteSystem] in {
673let Uses = [RAX, RBX, RCX, RDX], Defs = [RAX, RBX, RCX] in {
674  def GETSEC : I<0x37, RawFrm, (outs), (ins), "getsec", []>, PS;
675} // Uses, Defs
676} // SchedRW
677
678//===----------------------------------------------------------------------===//
679// TS flag control instruction.
680let SchedRW = [WriteSystem] in {
681def CLTS : I<0x06, RawFrm, (outs), (ins), "clts", []>, TB;
682}
683
684//===----------------------------------------------------------------------===//
685// IF (inside EFLAGS) management instructions.
686let SchedRW = [WriteSystem], Uses = [EFLAGS], Defs = [EFLAGS] in {
687def CLI : I<0xFA, RawFrm, (outs), (ins), "cli", []>;
688def STI : I<0xFB, RawFrm, (outs), (ins), "sti", []>;
689}
690
691//===----------------------------------------------------------------------===//
692// RDPID Instruction
693let SchedRW = [WriteSystem] in {
694def RDPID32 : I<0xC7, MRM7r, (outs GR32:$dst), (ins),
695                "rdpid\t$dst", [(set GR32:$dst, (int_x86_rdpid))]>, XS,
696                Requires<[Not64BitMode, HasRDPID]>;
697def RDPID64 : I<0xC7, MRM7r, (outs GR64:$dst), (ins), "rdpid\t$dst", []>, XS,
698                Requires<[In64BitMode, HasRDPID]>;
699} // SchedRW
700
701let Predicates = [In64BitMode, HasRDPID] in {
702  // Due to silly instruction definition, we have to compensate for the
703  // instruction outputing a 64-bit register.
704  def : Pat<(int_x86_rdpid),
705            (EXTRACT_SUBREG (RDPID64), sub_32bit)>;
706}
707
708
709//===----------------------------------------------------------------------===//
710// PTWRITE Instruction - Write Data to a Processor Trace Packet
711let SchedRW = [WriteSystem] in {
712def PTWRITEm: I<0xAE, MRM4m, (outs), (ins i32mem:$dst),
713                "ptwrite{l}\t$dst", [(int_x86_ptwrite32 (loadi32 addr:$dst))]>, XS,
714                Requires<[HasPTWRITE]>;
715def PTWRITE64m : RI<0xAE, MRM4m, (outs), (ins i64mem:$dst),
716                    "ptwrite{q}\t$dst", [(int_x86_ptwrite64 (loadi64 addr:$dst))]>, XS,
717                    Requires<[In64BitMode, HasPTWRITE]>;
718
719def PTWRITEr : I<0xAE, MRM4r, (outs), (ins GR32:$dst),
720                 "ptwrite{l}\t$dst", [(int_x86_ptwrite32 GR32:$dst)]>, XS,
721                    Requires<[HasPTWRITE]>;
722def PTWRITE64r : RI<0xAE, MRM4r, (outs), (ins GR64:$dst),
723                    "ptwrite{q}\t$dst", [(int_x86_ptwrite64 GR64:$dst)]>, XS,
724                    Requires<[In64BitMode, HasPTWRITE]>;
725} // SchedRW
726
727//===----------------------------------------------------------------------===//
728// Platform Configuration instruction
729
730// From ISA docs:
731//  "This instruction is used to execute functions for configuring platform
732//   features.
733//   EAX: Leaf function to be invoked.
734//   RBX/RCX/RDX: Leaf-specific purpose."
735//  "Successful execution of the leaf clears RAX (set to zero) and ZF, CF, PF,
736//   AF, OF, and SF are cleared. In case of failure, the failure reason is
737//   indicated in RAX with ZF set to 1 and CF, PF, AF, OF, and SF are cleared."
738// Thus all these mentioned registers are considered clobbered.
739
740let SchedRW = [WriteSystem] in {
741let Uses = [RAX, RBX, RCX, RDX], Defs = [RAX, RBX, RCX, RDX, EFLAGS] in
742    def PCONFIG : I<0x01, MRM_C5, (outs), (ins), "pconfig", []>, PS,
743                  Requires<[HasPCONFIG]>;
744} // SchedRW
745