1//=- SystemZScheduleZ196.td - SystemZ Scheduling Definitions ---*- tblgen -*-=//
2//
3//                     The LLVM Compiler Infrastructure
4//
5// This file is distributed under the University of Illinois Open Source
6// License. See LICENSE.TXT for details.
7//
8//===----------------------------------------------------------------------===//
9//
10// This file defines the machine model for Z196 to support instruction
11// scheduling and other instruction cost heuristics.
12//
13// Pseudos expanded right after isel do not need to be modelled here.
14//
15//===----------------------------------------------------------------------===//
16
17def Z196Model : SchedMachineModel {
18
19    let UnsupportedFeatures = Arch9UnsupportedFeatures.List;
20
21    let IssueWidth = 3;
22    let MicroOpBufferSize = 40;     // Issue queues
23    let LoadLatency = 1;            // Optimistic load latency.
24
25    let PostRAScheduler = 1;
26
27    // Extra cycles for a mispredicted branch.
28    let MispredictPenalty = 16;
29}
30
31let SchedModel = Z196Model in  {
32// These definitions need the SchedModel value. They could be put in a
33// subtarget common include file, but it seems the include system in Tablegen
34// currently (2016) rejects multiple includes of same file.
35
36// Decoder grouping rules
37let NumMicroOps = 1 in {
38  def : WriteRes<NormalGr, []>;
39  def : WriteRes<BeginGroup, []> { let BeginGroup  = 1; }
40  def : WriteRes<EndGroup, []>   { let EndGroup    = 1; }
41}
42def : WriteRes<GroupAlone, []> {
43  let NumMicroOps = 3;
44  let BeginGroup  = 1;
45  let EndGroup    = 1;
46}
47def : WriteRes<GroupAlone2, []> {
48  let NumMicroOps = 6;
49  let BeginGroup  = 1;
50  let EndGroup    = 1;
51}
52def : WriteRes<GroupAlone3, []> {
53  let NumMicroOps = 9;
54  let BeginGroup  = 1;
55  let EndGroup    = 1;
56}
57
58// Incoming latency removed from the register operand which is used together
59// with a memory operand by the instruction.
60def : ReadAdvance<RegReadAdv, 4>;
61
62// LoadLatency (above) is not used for instructions in this file. This is
63// instead the role of LSULatency, which is the latency value added to the
64// result of loads and instructions with folded memory operands.
65def : WriteRes<LSULatency, []> { let Latency = 4; let NumMicroOps = 0; }
66
67let NumMicroOps = 0 in {
68  foreach L = 1-30 in {
69    def : WriteRes<!cast<SchedWrite>("WLat"#L), []> { let Latency = L; }
70  }
71}
72
73// Execution units.
74def Z196_FXUnit : ProcResource<2>;
75def Z196_LSUnit : ProcResource<2>;
76def Z196_FPUnit : ProcResource<1>;
77def Z196_DFUnit : ProcResource<1>;
78def Z196_MCD    : ProcResource<1>;
79
80// Subtarget specific definitions of scheduling resources.
81let NumMicroOps = 0 in {
82  def : WriteRes<FXU, [Z196_FXUnit]>;
83  def : WriteRes<LSU, [Z196_LSUnit]>;
84  def : WriteRes<FPU, [Z196_FPUnit]>;
85  def : WriteRes<DFU, [Z196_DFUnit]>;
86  foreach Num = 2-6 in { let ResourceCycles = [Num] in {
87    def : WriteRes<!cast<SchedWrite>("FXU"#Num), [Z196_FXUnit]>;
88    def : WriteRes<!cast<SchedWrite>("LSU"#Num), [Z196_LSUnit]>;
89    def : WriteRes<!cast<SchedWrite>("FPU"#Num), [Z196_FPUnit]>;
90    def : WriteRes<!cast<SchedWrite>("DFU"#Num), [Z196_DFUnit]>;
91  }}
92}
93
94def : WriteRes<MCD, [Z196_MCD]> { let NumMicroOps = 3;
95                                  let BeginGroup  = 1;
96                                  let EndGroup    = 1; }
97
98// -------------------------- INSTRUCTIONS ---------------------------------- //
99
100// InstRW constructs have been used in order to preserve the
101// readability of the InstrInfo files.
102
103// For each instruction, as matched by a regexp, provide a list of
104// resources that it needs. These will be combined into a SchedClass.
105
106//===----------------------------------------------------------------------===//
107// Stack allocation
108//===----------------------------------------------------------------------===//
109
110def : InstRW<[WLat1, FXU, NormalGr], (instregex "ADJDYNALLOC$")>; // Pseudo -> LA / LAY
111
112//===----------------------------------------------------------------------===//
113// Branch instructions
114//===----------------------------------------------------------------------===//
115
116// Branch
117def : InstRW<[WLat1, LSU, EndGroup], (instregex "(Call)?BRC(L)?(Asm.*)?$")>;
118def : InstRW<[WLat1, LSU, EndGroup], (instregex "(Call)?J(G)?(Asm.*)?$")>;
119def : InstRW<[WLat1, LSU, EndGroup], (instregex "(Call)?BC(R)?(Asm.*)?$")>;
120def : InstRW<[WLat1, LSU, EndGroup], (instregex "(Call)?B(R)?(Asm.*)?$")>;
121def : InstRW<[WLat1, FXU, LSU, GroupAlone], (instregex "BRCT(G|H)?$")>;
122def : InstRW<[WLat1, FXU, LSU, GroupAlone], (instregex "BCT(G)?(R)?$")>;
123def : InstRW<[WLat1, FXU3, LSU, GroupAlone2],
124             (instregex "B(R)?X(H|L).*$")>;
125
126// Compare and branch
127def : InstRW<[WLat1, FXU, LSU, GroupAlone],
128             (instregex "C(L)?(G)?(I|R)J(Asm.*)?$")>;
129def : InstRW<[WLat1, FXU, LSU, GroupAlone],
130             (instregex "C(L)?(G)?(I|R)B(Call|Return|Asm.*)?$")>;
131
132//===----------------------------------------------------------------------===//
133// Trap instructions
134//===----------------------------------------------------------------------===//
135
136// Trap
137def : InstRW<[WLat1, LSU, EndGroup], (instregex "(Cond)?Trap$")>;
138
139// Compare and trap
140def : InstRW<[WLat1, FXU, NormalGr], (instregex "C(G)?(I|R)T(Asm.*)?$")>;
141def : InstRW<[WLat1, FXU, NormalGr], (instregex "CL(G)?RT(Asm.*)?$")>;
142def : InstRW<[WLat1, FXU, NormalGr], (instregex "CL(F|G)IT(Asm.*)?$")>;
143
144//===----------------------------------------------------------------------===//
145// Call and return instructions
146//===----------------------------------------------------------------------===//
147
148// Call
149def : InstRW<[WLat1, LSU, FXU2, GroupAlone], (instregex "(Call)?BRAS$")>;
150def : InstRW<[WLat1, LSU, FXU2, GroupAlone], (instregex "(Call)?BRASL$")>;
151def : InstRW<[WLat1, LSU, FXU2, GroupAlone], (instregex "(Call)?BAS(R)?$")>;
152def : InstRW<[WLat1, LSU, FXU2, GroupAlone], (instregex "TLS_(G|L)DCALL$")>;
153
154// Return
155def : InstRW<[WLat1, LSU, EndGroup], (instregex "Return$")>;
156def : InstRW<[WLat1, LSU, EndGroup], (instregex "CondReturn$")>;
157
158//===----------------------------------------------------------------------===//
159// Move instructions
160//===----------------------------------------------------------------------===//
161
162// Moves
163def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "MV(G|H)?HI$")>;
164def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "MVI(Y)?$")>;
165
166// Move character
167def : InstRW<[WLat1, FXU, LSU3, GroupAlone], (instregex "MVC$")>;
168def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "MVCL(E|U)?$")>;
169
170// Pseudo -> reg move
171def : InstRW<[WLat1, FXU, NormalGr], (instregex "COPY(_TO_REGCLASS)?$")>;
172def : InstRW<[WLat1, FXU, NormalGr], (instregex "EXTRACT_SUBREG$")>;
173def : InstRW<[WLat1, FXU, NormalGr], (instregex "INSERT_SUBREG$")>;
174def : InstRW<[WLat1, FXU, NormalGr], (instregex "REG_SEQUENCE$")>;
175
176// Loads
177def : InstRW<[LSULatency, LSU, NormalGr], (instregex "L(Y|FH|RL|Mux)?$")>;
178def : InstRW<[LSULatency, LSU, NormalGr], (instregex "LG(RL)?$")>;
179def : InstRW<[LSULatency, LSU, NormalGr], (instregex "L128$")>;
180
181def : InstRW<[WLat1, FXU, NormalGr], (instregex "LLIH(F|H|L)$")>;
182def : InstRW<[WLat1, FXU, NormalGr], (instregex "LLIL(F|H|L)$")>;
183
184def : InstRW<[WLat1, FXU, NormalGr], (instregex "LG(F|H)I$")>;
185def : InstRW<[WLat1, FXU, NormalGr], (instregex "LHI(Mux)?$")>;
186def : InstRW<[WLat1, FXU, NormalGr], (instregex "LR(Mux)?$")>;
187
188// Load and test
189def : InstRW<[WLat1LSU, WLat1LSU, LSU, FXU, NormalGr], (instregex "LT(G)?$")>;
190def : InstRW<[WLat1, FXU, NormalGr], (instregex "LT(G)?R$")>;
191
192// Stores
193def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "STG(RL)?$")>;
194def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "ST128$")>;
195def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "ST(Y|FH|RL|Mux)?$")>;
196
197// String moves.
198def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "MVST$")>;
199
200//===----------------------------------------------------------------------===//
201// Conditional move instructions
202//===----------------------------------------------------------------------===//
203
204def : InstRW<[WLat2, FXU, EndGroup], (instregex "LOC(G)?R(Asm.*)?$")>;
205def : InstRW<[WLat2LSU, RegReadAdv, FXU, LSU, EndGroup],
206             (instregex "LOC(G)?(Asm.*)?$")>;
207def : InstRW<[WLat1, FXU, LSU, EndGroup], (instregex "STOC(G)?(Asm.*)?$")>;
208
209//===----------------------------------------------------------------------===//
210// Sign extensions
211//===----------------------------------------------------------------------===//
212
213def : InstRW<[WLat1, FXU, NormalGr], (instregex "L(B|H|G)R$")>;
214def : InstRW<[WLat1, FXU, NormalGr], (instregex "LG(B|H|F)R$")>;
215
216def : InstRW<[WLat1LSU, WLat1LSU, FXU, LSU, NormalGr], (instregex "LTGF$")>;
217def : InstRW<[WLat1, FXU, NormalGr], (instregex "LTGFR$")>;
218
219def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "LB(H|Mux)?$")>;
220def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "LH(Y)?$")>;
221def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "LH(H|Mux|RL)$")>;
222def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "LG(B|H|F)$")>;
223def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "LG(H|F)RL$")>;
224
225//===----------------------------------------------------------------------===//
226// Zero extensions
227//===----------------------------------------------------------------------===//
228
229def : InstRW<[WLat1, FXU, NormalGr], (instregex "LLCR(Mux)?$")>;
230def : InstRW<[WLat1, FXU, NormalGr], (instregex "LLHR(Mux)?$")>;
231def : InstRW<[WLat1, FXU, NormalGr], (instregex "LLG(C|H|F|T)R$")>;
232def : InstRW<[LSULatency, LSU, NormalGr], (instregex "LLC(Mux)?$")>;
233def : InstRW<[LSULatency, LSU, NormalGr], (instregex "LLH(Mux)?$")>;
234def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "LL(C|H)H$")>;
235def : InstRW<[LSULatency, LSU, NormalGr], (instregex "LLHRL$")>;
236def : InstRW<[LSULatency, LSU, NormalGr], (instregex "LLG(C|H|F|T|HRL|FRL)$")>;
237
238//===----------------------------------------------------------------------===//
239// Truncations
240//===----------------------------------------------------------------------===//
241
242def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "STC(H|Y|Mux)?$")>;
243def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "STH(H|Y|RL|Mux)?$")>;
244def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "STCM(H|Y)?$")>;
245
246//===----------------------------------------------------------------------===//
247// Multi-register moves
248//===----------------------------------------------------------------------===//
249
250// Load multiple (estimated average of 5 ops)
251def : InstRW<[WLat10, WLat10, LSU5, GroupAlone], (instregex "LM(H|Y|G)?$")>;
252
253// Load multiple disjoint
254def : InstRW<[WLat30, WLat30, MCD], (instregex "LMD$")>;
255
256// Store multiple (estimated average of 3 ops)
257def : InstRW<[WLat1, LSU2, FXU5, GroupAlone], (instregex "STM(H|Y|G)?$")>;
258
259//===----------------------------------------------------------------------===//
260// Byte swaps
261//===----------------------------------------------------------------------===//
262
263def : InstRW<[WLat1, FXU, NormalGr], (instregex "LRV(G)?R$")>;
264def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "LRV(G|H)?$")>;
265def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "STRV(G|H)?$")>;
266def : InstRW<[WLat30, MCD], (instregex "MVCIN$")>;
267
268//===----------------------------------------------------------------------===//
269// Load address instructions
270//===----------------------------------------------------------------------===//
271
272def : InstRW<[WLat1, FXU, NormalGr], (instregex "LA(Y|RL)?$")>;
273
274// Load the Global Offset Table address
275def : InstRW<[WLat1, FXU, NormalGr], (instregex "GOT$")>;
276
277//===----------------------------------------------------------------------===//
278// Absolute and Negation
279//===----------------------------------------------------------------------===//
280
281def : InstRW<[WLat2, WLat2, FXU, NormalGr], (instregex "LP(G)?R$")>;
282def : InstRW<[WLat3, WLat3, FXU2, GroupAlone], (instregex "L(N|P)GFR$")>;
283def : InstRW<[WLat2, WLat2, FXU, NormalGr], (instregex "LN(R|GR)$")>;
284def : InstRW<[WLat1, FXU, NormalGr], (instregex "LC(R|GR)$")>;
285def : InstRW<[WLat2, WLat2, FXU2, GroupAlone], (instregex "LCGFR$")>;
286
287//===----------------------------------------------------------------------===//
288// Insertion
289//===----------------------------------------------------------------------===//
290
291def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "IC(Y)?$")>;
292def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
293             (instregex "IC32(Y)?$")>;
294def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
295             (instregex "ICM(H|Y)?$")>;
296def : InstRW<[WLat1, FXU, NormalGr], (instregex "II(F|H|L)Mux$")>;
297def : InstRW<[WLat1, FXU, NormalGr], (instregex "IIHF(64)?$")>;
298def : InstRW<[WLat1, FXU, NormalGr], (instregex "IIHH(64)?$")>;
299def : InstRW<[WLat1, FXU, NormalGr], (instregex "IIHL(64)?$")>;
300def : InstRW<[WLat1, FXU, NormalGr], (instregex "IILF(64)?$")>;
301def : InstRW<[WLat1, FXU, NormalGr], (instregex "IILH(64)?$")>;
302def : InstRW<[WLat1, FXU, NormalGr], (instregex "IILL(64)?$")>;
303
304//===----------------------------------------------------------------------===//
305// Addition
306//===----------------------------------------------------------------------===//
307
308def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
309             (instregex "A(L)?(Y)?$")>;
310def : InstRW<[WLat1LSU, WLat1LSU, FXU, LSU, NormalGr], (instregex "A(L)?SI$")>;
311def : InstRW<[WLat2LSU, WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone],
312             (instregex "AH(Y)?$")>;
313def : InstRW<[WLat1, FXU, NormalGr], (instregex "AIH$")>;
314def : InstRW<[WLat1, FXU, NormalGr], (instregex "AFI(Mux)?$")>;
315def : InstRW<[WLat1, FXU, NormalGr], (instregex "AGFI$")>;
316def : InstRW<[WLat1, FXU, NormalGr], (instregex "AGHI(K)?$")>;
317def : InstRW<[WLat1, FXU, NormalGr], (instregex "AGR(K)?$")>;
318def : InstRW<[WLat1, FXU, NormalGr], (instregex "AHI(K)?$")>;
319def : InstRW<[WLat1, FXU, NormalGr], (instregex "AHIMux(K)?$")>;
320def : InstRW<[WLat1, FXU, NormalGr], (instregex "AL(FI|HSIK)$")>;
321def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
322             (instregex "ALGF$")>;
323def : InstRW<[WLat1, FXU, NormalGr], (instregex "ALGHSIK$")>;
324def : InstRW<[WLat1, FXU, NormalGr], (instregex "ALGF(I|R)$")>;
325def : InstRW<[WLat1, FXU, NormalGr], (instregex "ALGR(K)?$")>;
326def : InstRW<[WLat1, FXU, NormalGr], (instregex "ALR(K)?$")>;
327def : InstRW<[WLat1, FXU, NormalGr], (instregex "AR(K)?$")>;
328def : InstRW<[WLat1, FXU, NormalGr], (instregex "A(L)?HHHR$")>;
329def : InstRW<[WLat2, WLat2, FXU2, GroupAlone], (instregex "A(L)?HHLR$")>;
330def : InstRW<[WLat1, FXU, NormalGr], (instregex "ALSIH(N)?$")>;
331def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
332             (instregex "A(L)?G$")>;
333def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "A(L)?GSI$")>;
334
335// Logical addition with carry
336def : InstRW<[WLat2LSU, WLat2LSU, RegReadAdv, FXU, LSU, GroupAlone],
337             (instregex "ALC(G)?$")>;
338def : InstRW<[WLat2, WLat2, FXU, GroupAlone], (instregex "ALC(G)?R$")>;
339
340// Add with sign extension (32 -> 64)
341def : InstRW<[WLat2LSU, WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone],
342             (instregex "AGF$")>;
343def : InstRW<[WLat2, WLat2, FXU2, GroupAlone], (instregex "AGFR$")>;
344
345//===----------------------------------------------------------------------===//
346// Subtraction
347//===----------------------------------------------------------------------===//
348
349def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
350             (instregex "S(G|Y)?$")>;
351def : InstRW<[WLat2LSU, WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone],
352             (instregex "SH(Y)?$")>;
353def : InstRW<[WLat1, FXU, NormalGr], (instregex "SGR(K)?$")>;
354def : InstRW<[WLat1, FXU, NormalGr], (instregex "SLFI$")>;
355def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
356             (instregex "SL(G|GF|Y)?$")>;
357def : InstRW<[WLat1, FXU, NormalGr], (instregex "SLGF(I|R)$")>;
358def : InstRW<[WLat1, FXU, NormalGr], (instregex "SLGR(K)?$")>;
359def : InstRW<[WLat1, FXU, NormalGr], (instregex "SLR(K)?$")>;
360def : InstRW<[WLat1, FXU, NormalGr], (instregex "SR(K)?$")>;
361def : InstRW<[WLat1, FXU, NormalGr], (instregex "S(L)?HHHR$")>;
362def : InstRW<[WLat2, WLat2, FXU2, GroupAlone], (instregex "S(L)?HHLR$")>;
363
364// Subtraction with borrow
365def : InstRW<[WLat2LSU, WLat2LSU, RegReadAdv, FXU, LSU, GroupAlone],
366             (instregex "SLB(G)?$")>;
367def : InstRW<[WLat2, WLat2, FXU, GroupAlone], (instregex "SLB(G)?R$")>;
368
369// Subtraction with sign extension (32 -> 64)
370def : InstRW<[WLat2LSU, WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone],
371             (instregex "SGF$")>;
372def : InstRW<[WLat2, WLat2, FXU2, GroupAlone], (instregex "SGFR$")>;
373
374//===----------------------------------------------------------------------===//
375// AND
376//===----------------------------------------------------------------------===//
377
378def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
379             (instregex "N(G|Y)?$")>;
380def : InstRW<[WLat1, FXU, NormalGr], (instregex "NGR(K)?$")>;
381def : InstRW<[WLat1, FXU, NormalGr], (instregex "NI(FMux|HMux|LMux)$")>;
382def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "NI(Y)?$")>;
383def : InstRW<[WLat1, FXU, NormalGr], (instregex "NIHF(64)?$")>;
384def : InstRW<[WLat1, FXU, NormalGr], (instregex "NIHH(64)?$")>;
385def : InstRW<[WLat1, FXU, NormalGr], (instregex "NIHL(64)?$")>;
386def : InstRW<[WLat1, FXU, NormalGr], (instregex "NILF(64)?$")>;
387def : InstRW<[WLat1, FXU, NormalGr], (instregex "NILH(64)?$")>;
388def : InstRW<[WLat1, FXU, NormalGr], (instregex "NILL(64)?$")>;
389def : InstRW<[WLat1, FXU, NormalGr], (instregex "NR(K)?$")>;
390def : InstRW<[WLat5LSU, LSU2, FXU, GroupAlone], (instregex "NC$")>;
391
392//===----------------------------------------------------------------------===//
393// OR
394//===----------------------------------------------------------------------===//
395
396def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
397             (instregex "O(G|Y)?$")>;
398def : InstRW<[WLat1, FXU, NormalGr], (instregex "OGR(K)?$")>;
399def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "OI(Y)?$")>;
400def : InstRW<[WLat1, FXU, NormalGr], (instregex "OI(FMux|HMux|LMux)$")>;
401def : InstRW<[WLat1, FXU, NormalGr], (instregex "OIHF(64)?$")>;
402def : InstRW<[WLat1, FXU, NormalGr], (instregex "OIHH(64)?$")>;
403def : InstRW<[WLat1, FXU, NormalGr], (instregex "OIHL(64)?$")>;
404def : InstRW<[WLat1, FXU, NormalGr], (instregex "OILF(64)?$")>;
405def : InstRW<[WLat1, FXU, NormalGr], (instregex "OILH(64)?$")>;
406def : InstRW<[WLat1, FXU, NormalGr], (instregex "OILL(64)?$")>;
407def : InstRW<[WLat1, FXU, NormalGr], (instregex "OR(K)?$")>;
408def : InstRW<[WLat5LSU, LSU2, FXU, GroupAlone], (instregex "OC$")>;
409
410//===----------------------------------------------------------------------===//
411// XOR
412//===----------------------------------------------------------------------===//
413
414def : InstRW<[WLat1LSU, WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
415             (instregex "X(G|Y)?$")>;
416def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "XI(Y)?$")>;
417def : InstRW<[WLat1, FXU, NormalGr], (instregex "XIFMux$")>;
418def : InstRW<[WLat1, FXU, NormalGr], (instregex "XGR(K)?$")>;
419def : InstRW<[WLat1, FXU, NormalGr], (instregex "XIHF(64)?$")>;
420def : InstRW<[WLat1, FXU, NormalGr], (instregex "XILF(64)?$")>;
421def : InstRW<[WLat1, FXU, NormalGr], (instregex "XR(K)?$")>;
422def : InstRW<[WLat5LSU, LSU2, FXU, GroupAlone], (instregex "XC$")>;
423
424//===----------------------------------------------------------------------===//
425// Multiplication
426//===----------------------------------------------------------------------===//
427
428def : InstRW<[WLat6LSU, RegReadAdv, FXU, LSU, NormalGr],
429             (instregex "MS(GF|Y)?$")>;
430def : InstRW<[WLat6, FXU, NormalGr], (instregex "MS(R|FI)$")>;
431def : InstRW<[WLat8LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "MSG$")>;
432def : InstRW<[WLat8, FXU, NormalGr], (instregex "MSGR$")>;
433def : InstRW<[WLat6, FXU, NormalGr], (instregex "MSGF(I|R)$")>;
434def : InstRW<[WLat11LSU, RegReadAdv, FXU2, LSU, GroupAlone],
435             (instregex "MLG$")>;
436def : InstRW<[WLat9, FXU2, GroupAlone], (instregex "MLGR$")>;
437def : InstRW<[WLat5, FXU, NormalGr], (instregex "MGHI$")>;
438def : InstRW<[WLat5, FXU, NormalGr], (instregex "MHI$")>;
439def : InstRW<[WLat5LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "MH(Y)?$")>;
440def : InstRW<[WLat7, FXU2, GroupAlone], (instregex "M(L)?R$")>;
441def : InstRW<[WLat7LSU, RegReadAdv, FXU2, LSU, GroupAlone],
442             (instregex "M(FY|L)?$")>;
443
444//===----------------------------------------------------------------------===//
445// Division and remainder
446//===----------------------------------------------------------------------===//
447
448def : InstRW<[WLat30, FPU4, FXU5, GroupAlone3], (instregex "DR$")>;
449def : InstRW<[WLat30, RegReadAdv, FPU4, LSU, FXU4, GroupAlone3],
450             (instregex "D$")>;
451def : InstRW<[WLat30, FPU4, FXU4, GroupAlone3], (instregex "DSG(F)?R$")>;
452def : InstRW<[WLat30, RegReadAdv, FPU4, LSU, FXU3, GroupAlone3],
453             (instregex "DSG(F)?$")>;
454def : InstRW<[WLat30, FPU4, FXU5, GroupAlone3], (instregex "DL(G)?R$")>;
455def : InstRW<[WLat30, RegReadAdv, FPU4, LSU, FXU4, GroupAlone3],
456             (instregex "DL(G)?$")>;
457
458//===----------------------------------------------------------------------===//
459// Shifts
460//===----------------------------------------------------------------------===//
461
462def : InstRW<[WLat1, FXU, NormalGr], (instregex "SLL(G|K)?$")>;
463def : InstRW<[WLat1, FXU, NormalGr], (instregex "SRL(G|K)?$")>;
464def : InstRW<[WLat1, FXU, NormalGr], (instregex "SRA(G|K)?$")>;
465def : InstRW<[WLat2, WLat2, FXU, NormalGr], (instregex "SLA(G|K)?$")>;
466def : InstRW<[WLat5LSU, WLat5LSU, FXU4, LSU, GroupAlone2],
467             (instregex "S(L|R)D(A|L)$")>;
468
469// Rotate
470def : InstRW<[WLat2LSU, FXU, LSU, NormalGr], (instregex "RLL(G)?$")>;
471
472// Rotate and insert
473def : InstRW<[WLat1, FXU, NormalGr], (instregex "RISBG(32)?$")>;
474def : InstRW<[WLat1, FXU, NormalGr], (instregex "RISBH(G|H|L)$")>;
475def : InstRW<[WLat1, FXU, NormalGr], (instregex "RISBL(G|H|L)$")>;
476def : InstRW<[WLat1, FXU, NormalGr], (instregex "RISBMux$")>;
477
478// Rotate and Select
479def : InstRW<[WLat3, WLat3, FXU2, GroupAlone], (instregex "R(N|O|X)SBG$")>;
480
481//===----------------------------------------------------------------------===//
482// Comparison
483//===----------------------------------------------------------------------===//
484
485def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "C(G|Y|Mux|RL)?$")>;
486def : InstRW<[WLat1, FXU, NormalGr], (instregex "C(F|H)I(Mux)?$")>;
487def : InstRW<[WLat1, FXU, NormalGr], (instregex "CG(F|H)I$")>;
488def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CG(HSI|RL)$")>;
489def : InstRW<[WLat1, FXU, NormalGr], (instregex "C(G)?R$")>;
490def : InstRW<[WLat1, FXU, NormalGr], (instregex "CIH$")>;
491def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "CHF$")>;
492def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CHSI$")>;
493def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr],
494             (instregex "CL(Y|Mux)?$")>;
495def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CLFHSI$")>;
496def : InstRW<[WLat1, FXU, NormalGr], (instregex "CLFI(Mux)?$")>;
497def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "CLG$")>;
498def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CLG(HRL|HSI)$")>;
499def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "CLGF$")>;
500def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CLGFRL$")>;
501def : InstRW<[WLat1, FXU, NormalGr], (instregex "CLGF(I|R)$")>;
502def : InstRW<[WLat1, FXU, NormalGr], (instregex "CLGR$")>;
503def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CLGRL$")>;
504def : InstRW<[WLat1LSU, RegReadAdv, FXU, LSU, NormalGr], (instregex "CLHF$")>;
505def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CLH(RL|HSI)$")>;
506def : InstRW<[WLat1, FXU, NormalGr], (instregex "CLIH$")>;
507def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CLI(Y)?$")>;
508def : InstRW<[WLat1, FXU, NormalGr], (instregex "CLR$")>;
509def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "CLRL$")>;
510def : InstRW<[WLat1, FXU, NormalGr], (instregex "C(L)?HHR$")>;
511def : InstRW<[WLat2, FXU2, GroupAlone], (instregex "C(L)?HLR$")>;
512
513// Compare halfword
514def : InstRW<[WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone],
515             (instregex "CH(Y)?$")>;
516def : InstRW<[WLat2LSU, FXU2, LSU, GroupAlone], (instregex "CHRL$")>;
517def : InstRW<[WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone], (instregex "CGH$")>;
518def : InstRW<[WLat2LSU, FXU2, LSU, GroupAlone], (instregex "CGHRL$")>;
519def : InstRW<[WLat2LSU, FXU2, LSU, GroupAlone], (instregex "CHHSI$")>;
520
521// Compare with sign extension (32 -> 64)
522def : InstRW<[WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone], (instregex "CGF$")>;
523def : InstRW<[WLat2LSU, FXU2, LSU, GroupAlone], (instregex "CGFRL$")>;
524def : InstRW<[WLat2, FXU2, GroupAlone], (instregex "CGFR$")>;
525
526// Compare logical character
527def : InstRW<[WLat9, FXU, LSU2, GroupAlone], (instregex "CLC$")>;
528def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "CLCL(E|U)?$")>;
529def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "CLST$")>;
530
531// Test under mask
532def : InstRW<[WLat1LSU, FXU, LSU, NormalGr], (instregex "TM(Y)?$")>;
533def : InstRW<[WLat1, FXU, NormalGr], (instregex "TM(H|L)Mux$")>;
534def : InstRW<[WLat1, FXU, NormalGr], (instregex "TMHH(64)?$")>;
535def : InstRW<[WLat1, FXU, NormalGr], (instregex "TMHL(64)?$")>;
536def : InstRW<[WLat1, FXU, NormalGr], (instregex "TMLH(64)?$")>;
537def : InstRW<[WLat1, FXU, NormalGr], (instregex "TMLL(64)?$")>;
538
539// Compare logical characters under mask
540def : InstRW<[WLat2LSU, RegReadAdv, FXU2, LSU, GroupAlone],
541             (instregex "CLM(H|Y)?$")>;
542
543//===----------------------------------------------------------------------===//
544// Prefetch
545//===----------------------------------------------------------------------===//
546
547def : InstRW<[WLat1, LSU, GroupAlone], (instregex "PFD(RL)?$")>;
548
549//===----------------------------------------------------------------------===//
550// Atomic operations
551//===----------------------------------------------------------------------===//
552
553def : InstRW<[WLat1, LSU, EndGroup], (instregex "Serialize$")>;
554
555def : InstRW<[WLat1LSU, WLat1LSU, FXU, LSU, NormalGr], (instregex "LAA(G)?$")>;
556def : InstRW<[WLat1LSU, WLat1LSU, FXU, LSU, NormalGr], (instregex "LAAL(G)?$")>;
557def : InstRW<[WLat1LSU, WLat1LSU, FXU, LSU, NormalGr], (instregex "LAN(G)?$")>;
558def : InstRW<[WLat1LSU, WLat1LSU, FXU, LSU, NormalGr], (instregex "LAO(G)?$")>;
559def : InstRW<[WLat1LSU, WLat1LSU, FXU, LSU, NormalGr], (instregex "LAX(G)?$")>;
560
561// Test and set
562def : InstRW<[WLat1LSU, FXU, LSU, EndGroup], (instregex "TS$")>;
563
564// Compare and swap
565def : InstRW<[WLat2LSU, WLat2LSU, FXU2, LSU, GroupAlone],
566             (instregex "CS(G|Y)?$")>;
567
568// Compare double and swap
569def : InstRW<[WLat5LSU, WLat5LSU, FXU5, LSU, GroupAlone2],
570             (instregex "CDS(Y)?$")>;
571def : InstRW<[WLat12, WLat12, FXU6, LSU2, GroupAlone],
572             (instregex "CDSG$")>;
573
574// Compare and swap and store
575def : InstRW<[WLat30, MCD], (instregex "CSST$")>;
576
577// Perform locked operation
578def : InstRW<[WLat30, MCD], (instregex "PLO$")>;
579
580// Load/store pair from/to quadword
581def : InstRW<[WLat4LSU, LSU2, GroupAlone], (instregex "LPQ$")>;
582def : InstRW<[WLat1, FXU2, LSU2, GroupAlone], (instregex "STPQ$")>;
583
584// Load pair disjoint
585def : InstRW<[WLat2LSU, WLat2LSU, LSU2, GroupAlone], (instregex "LPD(G)?$")>;
586
587//===----------------------------------------------------------------------===//
588// Translate and convert
589//===----------------------------------------------------------------------===//
590
591def : InstRW<[WLat30, MCD], (instregex "TR$")>;
592def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "TRT$")>;
593def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "TRTR$")>;
594def : InstRW<[WLat30, WLat30, MCD], (instregex "TRE$")>;
595def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "TRT(R)?E(Opt)?$")>;
596def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "TR(T|O)(T|O)(Opt)?$")>;
597def : InstRW<[WLat30, WLat30, WLat30, MCD],
598             (instregex "CU(12|14|21|24|41|42)(Opt)?$")>;
599def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "(CUUTF|CUTFU)(Opt)?$")>;
600
601//===----------------------------------------------------------------------===//
602// Message-security assist
603//===----------------------------------------------------------------------===//
604
605def : InstRW<[WLat30, WLat30, WLat30, WLat30, MCD],
606             (instregex "KM(C|F|O|CTR)?$")>;
607def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "(KIMD|KLMD|KMAC|PCC)$")>;
608
609//===----------------------------------------------------------------------===//
610// Decimal arithmetic
611//===----------------------------------------------------------------------===//
612
613def : InstRW<[WLat30, RegReadAdv, FXU, DFU2, LSU2, GroupAlone2],
614             (instregex "CVBG$")>;
615def : InstRW<[WLat20, RegReadAdv, FXU, DFU, LSU, GroupAlone2],
616             (instregex "CVB(Y)?$")>;
617def : InstRW<[WLat1, FXU3, DFU4, LSU, GroupAlone3], (instregex "CVDG$")>;
618def : InstRW<[WLat1, FXU2, DFU, LSU, GroupAlone3], (instregex "CVD(Y)?$")>;
619def : InstRW<[WLat1, LSU5, GroupAlone], (instregex "MV(N|O|Z)$")>;
620def : InstRW<[WLat1, LSU5, GroupAlone], (instregex "(PACK|PKA|PKU)$")>;
621def : InstRW<[WLat10, LSU5, GroupAlone], (instregex "UNPK(A|U)$")>;
622def : InstRW<[WLat1, LSU5, GroupAlone], (instregex "UNPK$")>;
623
624def : InstRW<[WLat11LSU, FXU, DFU4, LSU2, GroupAlone],
625             (instregex "(A|S|ZA)P$")>;
626def : InstRW<[WLat1, FXU, DFU4, LSU2, GroupAlone], (instregex "(M|D)P$")>;
627def : InstRW<[WLat15, FXU2, DFU4, LSU3, GroupAlone], (instregex "SRP$")>;
628def : InstRW<[WLat11, DFU4, LSU2, GroupAlone], (instregex "CP$")>;
629def : InstRW<[WLat5LSU, DFU2, LSU2, GroupAlone], (instregex "TP$")>;
630def : InstRW<[WLat30, MCD], (instregex "ED(MK)?$")>;
631
632//===----------------------------------------------------------------------===//
633// Access registers
634//===----------------------------------------------------------------------===//
635
636// Extract/set/copy access register
637def : InstRW<[WLat3, LSU, NormalGr], (instregex "(EAR|SAR|CPYA)$")>;
638
639// Load address extended
640def : InstRW<[WLat5, LSU, FXU, GroupAlone], (instregex "LAE(Y)?$")>;
641
642// Load/store access multiple (not modeled precisely)
643def : InstRW<[WLat10, WLat10, LSU5, GroupAlone], (instregex "LAM(Y)?$")>;
644def : InstRW<[WLat1, FXU5, LSU5, GroupAlone], (instregex "STAM(Y)?$")>;
645
646//===----------------------------------------------------------------------===//
647// Program mask and addressing mode
648//===----------------------------------------------------------------------===//
649
650// Insert Program Mask
651def : InstRW<[WLat3, FXU, EndGroup], (instregex "IPM$")>;
652
653// Set Program Mask
654def : InstRW<[WLat3, LSU, EndGroup], (instregex "SPM$")>;
655
656// Branch and link
657def : InstRW<[WLat1, FXU2, LSU, GroupAlone], (instregex "BAL(R)?$")>;
658
659// Test addressing mode
660def : InstRW<[WLat1, FXU, NormalGr], (instregex "TAM$")>;
661
662// Set addressing mode
663def : InstRW<[WLat1, LSU, EndGroup], (instregex "SAM(24|31|64)$")>;
664
665// Branch (and save) and set mode.
666def : InstRW<[WLat1, FXU, LSU, GroupAlone], (instregex "BSM$")>;
667def : InstRW<[WLat1, FXU2, LSU, GroupAlone], (instregex "BASSM$")>;
668
669//===----------------------------------------------------------------------===//
670// Miscellaneous Instructions.
671//===----------------------------------------------------------------------===//
672
673// Find leftmost one
674def : InstRW<[WLat7, WLat7, FXU2, GroupAlone], (instregex "FLOGR$")>;
675
676// Population count
677def : InstRW<[WLat3, WLat3, FXU, NormalGr], (instregex "POPCNT$")>;
678
679// String instructions
680def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "SRST(U)?$")>;
681def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "CUSE$")>;
682
683// Various complex instructions
684def : InstRW<[WLat30, WLat30, WLat30, WLat30, MCD], (instregex "CFC$")>;
685def : InstRW<[WLat30, WLat30, WLat30, WLat30, WLat30, WLat30, MCD],
686             (instregex "UPT$")>;
687def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "CKSM$")>;
688def : InstRW<[WLat30, WLat30, WLat30, WLat30, MCD], (instregex "CMPSC$")>;
689
690// Execute
691def : InstRW<[LSU, GroupAlone], (instregex "EX(RL)?$")>;
692
693//===----------------------------------------------------------------------===//
694// .insn directive instructions
695//===----------------------------------------------------------------------===//
696
697// An "empty" sched-class will be assigned instead of the "invalid sched-class".
698// getNumDecoderSlots() will then return 1 instead of 0.
699def : InstRW<[], (instregex "Insn.*")>;
700
701
702// ----------------------------- Floating point ----------------------------- //
703
704//===----------------------------------------------------------------------===//
705// FP: Move instructions
706//===----------------------------------------------------------------------===//
707
708// Load zero
709def : InstRW<[WLat1, FXU, NormalGr], (instregex "LZ(DR|ER)$")>;
710def : InstRW<[WLat2, FXU2, GroupAlone2], (instregex "LZXR$")>;
711
712// Load
713def : InstRW<[WLat1, FXU, NormalGr], (instregex "LER$")>;
714def : InstRW<[WLat1, FXU, NormalGr], (instregex "LD(R|R32|GR)$")>;
715def : InstRW<[WLat3, FXU, NormalGr], (instregex "LGDR$")>;
716def : InstRW<[WLat2, FXU2, GroupAlone2], (instregex "LXR$")>;
717
718// Load and Test
719def : InstRW<[WLat9, WLat9, FPU, NormalGr], (instregex "LT(E|D)BR$")>;
720def : InstRW<[WLat9, FPU, NormalGr], (instregex "LT(E|D)BRCompare$")>;
721def : InstRW<[WLat10, WLat10, FPU4, GroupAlone], (instregex "LTXBR(Compare)?$")>;
722
723// Copy sign
724def : InstRW<[WLat5, FXU2, GroupAlone], (instregex "CPSDR(d|s)(d|s)$")>;
725
726//===----------------------------------------------------------------------===//
727// FP: Load instructions
728//===----------------------------------------------------------------------===//
729
730def : InstRW<[LSULatency, LSU, NormalGr], (instregex "L(E|D)(Y|E32)?$")>;
731def : InstRW<[LSULatency, LSU, NormalGr], (instregex "LX$")>;
732
733//===----------------------------------------------------------------------===//
734// FP: Store instructions
735//===----------------------------------------------------------------------===//
736
737def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "ST(E|D)(Y)?$")>;
738def : InstRW<[WLat1, FXU, LSU, NormalGr], (instregex "STX$")>;
739
740//===----------------------------------------------------------------------===//
741// FP: Conversion instructions
742//===----------------------------------------------------------------------===//
743
744// Load rounded
745def : InstRW<[WLat7, FPU, NormalGr], (instregex "LEDBR(A)?$")>;
746def : InstRW<[WLat9, FPU2, NormalGr], (instregex "L(E|D)XBR(A)?$")>;
747
748// Load lengthened
749def : InstRW<[WLat7LSU, FPU, LSU, NormalGr], (instregex "LDEB$")>;
750def : InstRW<[WLat7, FPU, NormalGr], (instregex "LDEBR$")>;
751def : InstRW<[WLat11LSU, FPU4, LSU, GroupAlone], (instregex "LX(E|D)B$")>;
752def : InstRW<[WLat10, FPU4, GroupAlone], (instregex "LX(E|D)BR$")>;
753
754// Convert from fixed / logical
755def : InstRW<[WLat8, FXU, FPU, GroupAlone], (instregex "C(E|D)(F|G)BR(A)?$")>;
756def : InstRW<[WLat11, FXU, FPU4, GroupAlone2], (instregex "CX(F|G)BR(A?)$")>;
757def : InstRW<[WLat8, FXU, FPU, GroupAlone], (instregex "CEL(F|G)BR$")>;
758def : InstRW<[WLat8, FXU, FPU, GroupAlone], (instregex "CDL(F|G)BR$")>;
759def : InstRW<[WLat11, FXU, FPU4, GroupAlone2], (instregex "CXL(F|G)BR$")>;
760
761// Convert to fixed / logical
762def : InstRW<[WLat12, WLat12, FXU, FPU, GroupAlone],
763             (instregex "C(F|G)(E|D)BR(A?)$")>;
764def : InstRW<[WLat12, WLat12, FXU, FPU2, GroupAlone],
765             (instregex "C(F|G)XBR(A?)$")>;
766def : InstRW<[WLat12, WLat12, FXU, FPU, GroupAlone],
767             (instregex "CL(F|G)(E|D)BR$")>;
768def : InstRW<[WLat12, WLat12, FXU, FPU2, GroupAlone], (instregex "CL(F|G)XBR$")>;
769
770//===----------------------------------------------------------------------===//
771// FP: Unary arithmetic
772//===----------------------------------------------------------------------===//
773
774// Load Complement / Negative / Positive
775def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "L(C|N|P)(E|D)BR$")>;
776def : InstRW<[WLat1, FXU, NormalGr], (instregex "L(C|N|P)DFR(_32)?$")>;
777def : InstRW<[WLat10, WLat10, FPU4, GroupAlone], (instregex "L(C|N|P)XBR$")>;
778
779// Square root
780def : InstRW<[WLat30, FPU, LSU, NormalGr], (instregex "SQ(E|D)B$")>;
781def : InstRW<[WLat30, FPU, NormalGr], (instregex "SQ(E|D)BR$")>;
782def : InstRW<[WLat30, FPU4, GroupAlone], (instregex "SQXBR$")>;
783
784// Load FP integer
785def : InstRW<[WLat7, FPU, NormalGr], (instregex "FI(E|D)BR(A)?$")>;
786def : InstRW<[WLat15, FPU4, GroupAlone], (instregex "FIXBR(A)?$")>;
787
788//===----------------------------------------------------------------------===//
789// FP: Binary arithmetic
790//===----------------------------------------------------------------------===//
791
792// Addition
793def : InstRW<[WLat7LSU, WLat7LSU, RegReadAdv, FPU, LSU, NormalGr],
794             (instregex "A(E|D)B$")>;
795def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "A(E|D)BR$")>;
796def : InstRW<[WLat20, WLat20, FPU4, GroupAlone], (instregex "AXBR$")>;
797
798// Subtraction
799def : InstRW<[WLat7LSU, WLat7LSU, RegReadAdv, FPU, LSU, NormalGr],
800             (instregex "S(E|D)B$")>;
801def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "S(E|D)BR$")>;
802def : InstRW<[WLat20, WLat20, FPU4, GroupAlone], (instregex "SXBR$")>;
803
804// Multiply
805def : InstRW<[WLat7LSU, RegReadAdv, FPU, LSU, NormalGr],
806             (instregex "M(D|DE|EE)B$")>;
807def : InstRW<[WLat7, FPU, NormalGr], (instregex "M(D|DE|EE)BR$")>;
808def : InstRW<[WLat11LSU, RegReadAdv, FPU4, LSU, GroupAlone],
809             (instregex "MXDB$")>;
810def : InstRW<[WLat10, FPU4, GroupAlone], (instregex "MXDBR$")>;
811def : InstRW<[WLat30, FPU4, GroupAlone], (instregex "MXBR$")>;
812
813// Multiply and add / subtract
814def : InstRW<[WLat7LSU, RegReadAdv, RegReadAdv, FPU2, LSU, GroupAlone],
815             (instregex "M(A|S)EB$")>;
816def : InstRW<[WLat7, FPU, GroupAlone], (instregex "M(A|S)EBR$")>;
817def : InstRW<[WLat7LSU, RegReadAdv, RegReadAdv, FPU2, LSU, GroupAlone],
818             (instregex "M(A|S)DB$")>;
819def : InstRW<[WLat7, FPU, GroupAlone], (instregex "M(A|S)DBR$")>;
820
821// Division
822def : InstRW<[WLat30, RegReadAdv, FPU, LSU, NormalGr], (instregex "D(E|D)B$")>;
823def : InstRW<[WLat30, FPU, NormalGr], (instregex "D(E|D)BR$")>;
824def : InstRW<[WLat30, FPU4, GroupAlone], (instregex "DXBR$")>;
825
826// Divide to integer
827def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "DI(E|D)BR$")>;
828
829//===----------------------------------------------------------------------===//
830// FP: Comparisons
831//===----------------------------------------------------------------------===//
832
833// Compare
834def : InstRW<[WLat11LSU, RegReadAdv, FPU, LSU, NormalGr],
835             (instregex "(K|C)(E|D)B$")>;
836def : InstRW<[WLat9, FPU, NormalGr], (instregex "(K|C)(E|D)BR$")>;
837def : InstRW<[WLat30, FPU2, NormalGr], (instregex "(K|C)XBR$")>;
838
839// Test Data Class
840def : InstRW<[WLat15, FPU, LSU, NormalGr], (instregex "TC(E|D)B$")>;
841def : InstRW<[WLat15, FPU4, LSU, GroupAlone], (instregex "TCXB$")>;
842
843//===----------------------------------------------------------------------===//
844// FP: Floating-point control register instructions
845//===----------------------------------------------------------------------===//
846
847def : InstRW<[WLat4, FXU, LSU, GroupAlone], (instregex "EFPC$")>;
848def : InstRW<[WLat1, FXU, LSU, GroupAlone], (instregex "STFPC$")>;
849def : InstRW<[WLat1, LSU, GroupAlone], (instregex "SFPC$")>;
850def : InstRW<[WLat1, LSU2, GroupAlone], (instregex "LFPC$")>;
851def : InstRW<[WLat30, MCD], (instregex "SFASR$")>;
852def : InstRW<[WLat30, MCD], (instregex "LFAS$")>;
853def : InstRW<[WLat2, FXU, GroupAlone], (instregex "SRNM(B|T)?$")>;
854
855
856// --------------------- Hexadecimal floating point ------------------------- //
857
858//===----------------------------------------------------------------------===//
859// HFP: Move instructions
860//===----------------------------------------------------------------------===//
861
862// Load and Test
863def : InstRW<[WLat9, WLat9, FPU, NormalGr], (instregex "LT(E|D)R$")>;
864def : InstRW<[WLat9, WLat9, FPU4, GroupAlone], (instregex "LTXR$")>;
865
866//===----------------------------------------------------------------------===//
867// HFP: Conversion instructions
868//===----------------------------------------------------------------------===//
869
870// Load rounded
871def : InstRW<[WLat7, FPU, NormalGr], (instregex "(LEDR|LRER)$")>;
872def : InstRW<[WLat7, FPU, NormalGr], (instregex "LEXR$")>;
873def : InstRW<[WLat9, FPU, NormalGr], (instregex "(LDXR|LRDR)$")>;
874
875// Load lengthened
876def : InstRW<[LSULatency, LSU, NormalGr], (instregex "LDE$")>;
877def : InstRW<[WLat1, FXU, NormalGr], (instregex "LDER$")>;
878def : InstRW<[WLat11LSU, FPU4, LSU, GroupAlone], (instregex "LX(E|D)$")>;
879def : InstRW<[WLat9, FPU4, GroupAlone], (instregex "LX(E|D)R$")>;
880
881// Convert from fixed
882def : InstRW<[WLat8, FXU, FPU, GroupAlone], (instregex "C(E|D)(F|G)R$")>;
883def : InstRW<[WLat10, FXU, FPU4, GroupAlone2], (instregex "CX(F|G)R$")>;
884
885// Convert to fixed
886def : InstRW<[WLat12, WLat12, FXU, FPU, GroupAlone],
887             (instregex "C(F|G)(E|D)R$")>;
888def : InstRW<[WLat30, WLat30, FXU, FPU2, GroupAlone], (instregex "C(F|G)XR$")>;
889
890// Convert BFP to HFP / HFP to BFP.
891def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "THD(E)?R$")>;
892def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "TB(E)?DR$")>;
893
894//===----------------------------------------------------------------------===//
895// HFP: Unary arithmetic
896//===----------------------------------------------------------------------===//
897
898// Load Complement / Negative / Positive
899def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "L(C|N|P)(E|D)R$")>;
900def : InstRW<[WLat9, WLat9, FPU4, GroupAlone], (instregex "L(C|N|P)XR$")>;
901
902// Halve
903def : InstRW<[WLat7, FPU, NormalGr], (instregex "H(E|D)R$")>;
904
905// Square root
906def : InstRW<[WLat30, FPU, LSU, NormalGr], (instregex "SQ(E|D)$")>;
907def : InstRW<[WLat30, FPU, NormalGr], (instregex "SQ(E|D)R$")>;
908def : InstRW<[WLat30, FPU4, GroupAlone], (instregex "SQXR$")>;
909
910// Load FP integer
911def : InstRW<[WLat7, FPU, NormalGr], (instregex "FI(E|D)R$")>;
912def : InstRW<[WLat15, FPU4, GroupAlone], (instregex "FIXR$")>;
913
914//===----------------------------------------------------------------------===//
915// HFP: Binary arithmetic
916//===----------------------------------------------------------------------===//
917
918// Addition
919def : InstRW<[WLat7LSU, WLat7LSU, RegReadAdv, FPU, LSU, NormalGr],
920             (instregex "A(E|D|U|W)$")>;
921def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "A(E|D|U|W)R$")>;
922def : InstRW<[WLat15, WLat15, FPU4, GroupAlone], (instregex "AXR$")>;
923
924// Subtraction
925def : InstRW<[WLat7LSU, WLat7LSU, RegReadAdv, FPU, LSU, NormalGr],
926             (instregex "S(E|D|U|W)$")>;
927def : InstRW<[WLat7, WLat7, FPU, NormalGr], (instregex "S(E|D|U|W)R$")>;
928def : InstRW<[WLat15, WLat15, FPU4, GroupAlone], (instregex "SXR$")>;
929
930// Multiply
931def : InstRW<[WLat7LSU, RegReadAdv, FPU, LSU, NormalGr], (instregex "M(D|EE)$")>;
932def : InstRW<[WLat8LSU, RegReadAdv, FPU, LSU, NormalGr], (instregex "M(DE|E)$")>;
933def : InstRW<[WLat7, FPU, NormalGr], (instregex "M(D|EE)R$")>;
934def : InstRW<[WLat8, FPU, NormalGr], (instregex "M(DE|E)R$")>;
935def : InstRW<[WLat11LSU, RegReadAdv, FPU4, LSU, GroupAlone], (instregex "MXD$")>;
936def : InstRW<[WLat10, FPU4, GroupAlone], (instregex "MXDR$")>;
937def : InstRW<[WLat30, FPU4, GroupAlone], (instregex "MXR$")>;
938def : InstRW<[WLat11LSU, RegReadAdv, FPU4, LSU, GroupAlone], (instregex "MY$")>;
939def : InstRW<[WLat7LSU, RegReadAdv, FPU2, LSU, GroupAlone],
940             (instregex "MY(H|L)$")>;
941def : InstRW<[WLat10, FPU4, GroupAlone], (instregex "MYR$")>;
942def : InstRW<[WLat7, FPU, GroupAlone], (instregex "MY(H|L)R$")>;
943
944// Multiply and add / subtract
945def : InstRW<[WLat7LSU, RegReadAdv, RegReadAdv, FPU2, LSU, GroupAlone],
946             (instregex "M(A|S)(E|D)$")>;
947def : InstRW<[WLat7, FPU, GroupAlone], (instregex "M(A|S)(E|D)R$")>;
948def : InstRW<[WLat11LSU, RegReadAdv, RegReadAdv, FPU4, LSU, GroupAlone],
949             (instregex "MAY$")>;
950def : InstRW<[WLat7LSU, RegReadAdv, RegReadAdv, FPU2, LSU, GroupAlone],
951             (instregex "MAY(H|L)$")>;
952def : InstRW<[WLat10, FPU4, GroupAlone], (instregex "MAYR$")>;
953def : InstRW<[WLat7, FPU, GroupAlone], (instregex "MAY(H|L)R$")>;
954
955// Division
956def : InstRW<[WLat30, RegReadAdv, FPU, LSU, NormalGr], (instregex "D(E|D)$")>;
957def : InstRW<[WLat30, FPU, NormalGr], (instregex "D(E|D)R$")>;
958def : InstRW<[WLat30, FPU4, GroupAlone], (instregex "DXR$")>;
959
960//===----------------------------------------------------------------------===//
961// HFP: Comparisons
962//===----------------------------------------------------------------------===//
963
964// Compare
965def : InstRW<[WLat11LSU, RegReadAdv, FPU, LSU, NormalGr], (instregex "C(E|D)$")>;
966def : InstRW<[WLat9, FPU, NormalGr], (instregex "C(E|D)R$")>;
967def : InstRW<[WLat15, FPU2, NormalGr], (instregex "CXR$")>;
968
969
970// ------------------------ Decimal floating point -------------------------- //
971
972//===----------------------------------------------------------------------===//
973// DFP: Move instructions
974//===----------------------------------------------------------------------===//
975
976// Load and Test
977def : InstRW<[WLat4, WLat4, DFU, NormalGr], (instregex "LTDTR$")>;
978def : InstRW<[WLat6, WLat6, DFU4, GroupAlone], (instregex "LTXTR$")>;
979
980//===----------------------------------------------------------------------===//
981// DFP: Conversion instructions
982//===----------------------------------------------------------------------===//
983
984// Load rounded
985def : InstRW<[WLat30, DFU, NormalGr], (instregex "LEDTR$")>;
986def : InstRW<[WLat30, DFU2, NormalGr], (instregex "LDXTR$")>;
987
988// Load lengthened
989def : InstRW<[WLat7, DFU, NormalGr], (instregex "LDETR$")>;
990def : InstRW<[WLat6, DFU4, GroupAlone], (instregex "LXDTR$")>;
991
992// Convert from fixed / logical
993def : InstRW<[WLat9, FXU, DFU, GroupAlone], (instregex "CDFTR$")>;
994def : InstRW<[WLat30, FXU, DFU, GroupAlone], (instregex "CDGTR(A)?$")>;
995def : InstRW<[WLat5, FXU, DFU4, GroupAlone2], (instregex "CXFTR(A)?$")>;
996def : InstRW<[WLat30, FXU, DFU4, GroupAlone2], (instregex "CXGTR(A)?$")>;
997def : InstRW<[WLat9, FXU, DFU, GroupAlone], (instregex "CDL(F|G)TR$")>;
998def : InstRW<[WLat9, FXU, DFU4, GroupAlone2], (instregex "CXLFTR$")>;
999def : InstRW<[WLat5, FXU, DFU4, GroupAlone2], (instregex "CXLGTR$")>;
1000
1001// Convert to fixed / logical
1002def : InstRW<[WLat11, WLat11, FXU, DFU, GroupAlone], (instregex "CFDTR(A)?$")>;
1003def : InstRW<[WLat30, WLat30, FXU, DFU, GroupAlone], (instregex "CGDTR(A)?$")>;
1004def : InstRW<[WLat7, WLat7, FXU, DFU2, GroupAlone], (instregex "CFXTR$")>;
1005def : InstRW<[WLat30, WLat30, FXU, DFU2, GroupAlone], (instregex "CGXTR(A)?$")>;
1006def : InstRW<[WLat11, WLat11, FXU, DFU, GroupAlone], (instregex "CL(F|G)DTR$")>;
1007def : InstRW<[WLat7, WLat7, FXU, DFU2, GroupAlone], (instregex "CL(F|G)XTR$")>;
1008
1009// Convert from / to signed / unsigned packed
1010def : InstRW<[WLat5, FXU, DFU, GroupAlone], (instregex "CD(S|U)TR$")>;
1011def : InstRW<[WLat8, FXU2, DFU4, GroupAlone2], (instregex "CX(S|U)TR$")>;
1012def : InstRW<[WLat7, FXU, DFU, GroupAlone], (instregex "C(S|U)DTR$")>;
1013def : InstRW<[WLat12, FXU2, DFU4, GroupAlone2], (instregex "C(S|U)XTR$")>;
1014
1015// Perform floating-point operation
1016def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "PFPO$")>;
1017
1018//===----------------------------------------------------------------------===//
1019// DFP: Unary arithmetic
1020//===----------------------------------------------------------------------===//
1021
1022// Load FP integer
1023def : InstRW<[WLat8, DFU, NormalGr], (instregex "FIDTR$")>;
1024def : InstRW<[WLat10, DFU4, GroupAlone], (instregex "FIXTR$")>;
1025
1026// Extract biased exponent
1027def : InstRW<[WLat7, FXU, DFU, GroupAlone], (instregex "EEDTR$")>;
1028def : InstRW<[WLat8, FXU, DFU2, GroupAlone], (instregex "EEXTR$")>;
1029
1030// Extract significance
1031def : InstRW<[WLat7, FXU, DFU, GroupAlone], (instregex "ESDTR$")>;
1032def : InstRW<[WLat8, FXU, DFU2, GroupAlone], (instregex "ESXTR$")>;
1033
1034//===----------------------------------------------------------------------===//
1035// DFP: Binary arithmetic
1036//===----------------------------------------------------------------------===//
1037
1038// Addition
1039def : InstRW<[WLat9, WLat9, DFU, NormalGr], (instregex "ADTR(A)?$")>;
1040def : InstRW<[WLat30, WLat30, DFU4, GroupAlone], (instregex "AXTR(A)?$")>;
1041
1042// Subtraction
1043def : InstRW<[WLat9, WLat9, DFU, NormalGr], (instregex "SDTR(A)?$")>;
1044def : InstRW<[WLat30, WLat30, DFU4, GroupAlone], (instregex "SXTR(A)?$")>;
1045
1046// Multiply
1047def : InstRW<[WLat30, DFU, NormalGr], (instregex "MDTR(A)?$")>;
1048def : InstRW<[WLat30, DFU4, GroupAlone], (instregex "MXTR(A)?$")>;
1049
1050// Division
1051def : InstRW<[WLat30, DFU, NormalGr], (instregex "DDTR(A)?$")>;
1052def : InstRW<[WLat30, DFU4, GroupAlone], (instregex "DXTR(A)?$")>;
1053
1054// Quantize
1055def : InstRW<[WLat8, WLat8, DFU, NormalGr], (instregex "QADTR$")>;
1056def : InstRW<[WLat10, WLat10, DFU4, GroupAlone], (instregex "QAXTR$")>;
1057
1058// Reround
1059def : InstRW<[WLat11, WLat11, FXU, DFU, GroupAlone], (instregex "RRDTR$")>;
1060def : InstRW<[WLat30, WLat30, FXU, DFU4, GroupAlone2], (instregex "RRXTR$")>;
1061
1062// Shift significand left/right
1063def : InstRW<[WLat7LSU, LSU, DFU, GroupAlone], (instregex "S(L|R)DT$")>;
1064def : InstRW<[WLat11LSU, LSU, DFU4, GroupAlone], (instregex "S(L|R)XT$")>;
1065
1066// Insert biased exponent
1067def : InstRW<[WLat5, FXU, DFU, GroupAlone], (instregex "IEDTR$")>;
1068def : InstRW<[WLat7, FXU, DFU4, GroupAlone2], (instregex "IEXTR$")>;
1069
1070//===----------------------------------------------------------------------===//
1071// DFP: Comparisons
1072//===----------------------------------------------------------------------===//
1073
1074// Compare
1075def : InstRW<[WLat9, DFU, NormalGr], (instregex "(K|C)DTR$")>;
1076def : InstRW<[WLat10, DFU2, NormalGr], (instregex "(K|C)XTR$")>;
1077
1078// Compare biased exponent
1079def : InstRW<[WLat4, DFU, NormalGr], (instregex "CEDTR$")>;
1080def : InstRW<[WLat5, DFU2, NormalGr], (instregex "CEXTR$")>;
1081
1082// Test Data Class/Group
1083def : InstRW<[WLat9, LSU, DFU, NormalGr], (instregex "TD(C|G)DT$")>;
1084def : InstRW<[WLat10, LSU, DFU, NormalGr], (instregex "TD(C|G)ET$")>;
1085def : InstRW<[WLat10, LSU, DFU2, NormalGr], (instregex "TD(C|G)XT$")>;
1086
1087
1088// -------------------------------- System ---------------------------------- //
1089
1090//===----------------------------------------------------------------------===//
1091// System: Program-Status Word Instructions
1092//===----------------------------------------------------------------------===//
1093
1094def : InstRW<[WLat30, WLat30, MCD], (instregex "EPSW$")>;
1095def : InstRW<[WLat30, MCD], (instregex "LPSW(E)?$")>;
1096def : InstRW<[WLat3, FXU, GroupAlone], (instregex "IPK$")>;
1097def : InstRW<[WLat1, LSU, EndGroup], (instregex "SPKA$")>;
1098def : InstRW<[WLat1, LSU, EndGroup], (instregex "SSM$")>;
1099def : InstRW<[WLat1, FXU, LSU, GroupAlone], (instregex "ST(N|O)SM$")>;
1100def : InstRW<[WLat3, FXU, NormalGr], (instregex "IAC$")>;
1101def : InstRW<[WLat1, LSU, EndGroup], (instregex "SAC(F)?$")>;
1102
1103//===----------------------------------------------------------------------===//
1104// System: Control Register Instructions
1105//===----------------------------------------------------------------------===//
1106
1107def : InstRW<[WLat10, WLat10, LSU2, GroupAlone], (instregex "LCTL(G)?$")>;
1108def : InstRW<[WLat1, FXU5, LSU5, GroupAlone], (instregex "STCT(L|G)$")>;
1109def : InstRW<[LSULatency, LSU, NormalGr], (instregex "E(P|S)A(I)?R$")>;
1110def : InstRW<[WLat30, MCD], (instregex "SSA(I)?R$")>;
1111def : InstRW<[WLat30, MCD], (instregex "ESEA$")>;
1112
1113//===----------------------------------------------------------------------===//
1114// System: Prefix-Register Instructions
1115//===----------------------------------------------------------------------===//
1116
1117def : InstRW<[WLat30, MCD], (instregex "S(T)?PX$")>;
1118
1119//===----------------------------------------------------------------------===//
1120// System: Storage-Key and Real Memory Instructions
1121//===----------------------------------------------------------------------===//
1122
1123def : InstRW<[WLat30, MCD], (instregex "ISKE$")>;
1124def : InstRW<[WLat30, MCD], (instregex "IVSK$")>;
1125def : InstRW<[WLat30, MCD], (instregex "SSKE(Opt)?$")>;
1126def : InstRW<[WLat30, MCD], (instregex "RRB(E|M)$")>;
1127def : InstRW<[WLat30, MCD], (instregex "PFMF$")>;
1128def : InstRW<[WLat30, WLat30, MCD], (instregex "TB$")>;
1129def : InstRW<[WLat30, MCD], (instregex "PGIN$")>;
1130def : InstRW<[WLat30, MCD], (instregex "PGOUT$")>;
1131
1132//===----------------------------------------------------------------------===//
1133// System: Dynamic-Address-Translation Instructions
1134//===----------------------------------------------------------------------===//
1135
1136def : InstRW<[WLat30, MCD], (instregex "IPTE(Opt)?(Opt)?$")>;
1137def : InstRW<[WLat30, MCD], (instregex "IDTE(Opt)?$")>;
1138def : InstRW<[WLat30, MCD], (instregex "PTLB$")>;
1139def : InstRW<[WLat30, WLat30, MCD], (instregex "CSP(G)?$")>;
1140def : InstRW<[WLat30, WLat30, WLat30, MCD], (instregex "LPTEA$")>;
1141def : InstRW<[WLat30, WLat30, MCD], (instregex "LRA(Y|G)?$")>;
1142def : InstRW<[WLat30, MCD], (instregex "STRAG$")>;
1143def : InstRW<[WLat30, MCD], (instregex "LURA(G)?$")>;
1144def : InstRW<[WLat30, MCD], (instregex "STUR(A|G)$")>;
1145def : InstRW<[WLat30, MCD], (instregex "TPROT$")>;
1146
1147//===----------------------------------------------------------------------===//
1148// System: Memory-move Instructions
1149//===----------------------------------------------------------------------===//
1150
1151def : InstRW<[WLat30, MCD], (instregex "MVC(K|P|S)$")>;
1152def : InstRW<[WLat30, MCD], (instregex "MVC(S|D)K$")>;
1153def : InstRW<[WLat30, MCD], (instregex "MVCOS$")>;
1154def : InstRW<[WLat30, MCD], (instregex "MVPG$")>;
1155
1156//===----------------------------------------------------------------------===//
1157// System: Address-Space Instructions
1158//===----------------------------------------------------------------------===//
1159
1160def : InstRW<[WLat30, MCD], (instregex "LASP$")>;
1161def : InstRW<[WLat1, LSU, GroupAlone], (instregex "PALB$")>;
1162def : InstRW<[WLat30, MCD], (instregex "PC$")>;
1163def : InstRW<[WLat30, MCD], (instregex "PR$")>;
1164def : InstRW<[WLat30, MCD], (instregex "PT(I)?$")>;
1165def : InstRW<[WLat30, MCD], (instregex "RP$")>;
1166def : InstRW<[WLat30, MCD], (instregex "BS(G|A)$")>;
1167def : InstRW<[WLat30, MCD], (instregex "TAR$")>;
1168
1169//===----------------------------------------------------------------------===//
1170// System: Linkage-Stack Instructions
1171//===----------------------------------------------------------------------===//
1172
1173def : InstRW<[WLat30, MCD], (instregex "BAKR$")>;
1174def : InstRW<[WLat30, MCD], (instregex "EREG(G)?$")>;
1175def : InstRW<[WLat30, WLat30, MCD], (instregex "(E|M)STA$")>;
1176
1177//===----------------------------------------------------------------------===//
1178// System: Time-Related Instructions
1179//===----------------------------------------------------------------------===//
1180
1181def : InstRW<[WLat30, MCD], (instregex "PTFF$")>;
1182def : InstRW<[WLat30, MCD], (instregex "SCK$")>;
1183def : InstRW<[WLat30, MCD], (instregex "SCKPF$")>;
1184def : InstRW<[WLat30, MCD], (instregex "SCKC$")>;
1185def : InstRW<[WLat30, MCD], (instregex "SPT$")>;
1186def : InstRW<[WLat30, MCD], (instregex "STCK(F)?$")>;
1187def : InstRW<[WLat30, MCD], (instregex "STCKE$")>;
1188def : InstRW<[WLat30, MCD], (instregex "STCKC$")>;
1189def : InstRW<[WLat30, MCD], (instregex "STPT$")>;
1190
1191//===----------------------------------------------------------------------===//
1192// System: CPU-Related Instructions
1193//===----------------------------------------------------------------------===//
1194
1195def : InstRW<[WLat30, MCD], (instregex "STAP$")>;
1196def : InstRW<[WLat30, MCD], (instregex "STIDP$")>;
1197def : InstRW<[WLat30, WLat30, MCD], (instregex "STSI$")>;
1198def : InstRW<[WLat30, WLat30, MCD], (instregex "STFL(E)?$")>;
1199def : InstRW<[WLat30, MCD], (instregex "ECAG$")>;
1200def : InstRW<[WLat30, WLat30, MCD], (instregex "ECTG$")>;
1201def : InstRW<[WLat30, MCD], (instregex "PTF$")>;
1202def : InstRW<[WLat30, MCD], (instregex "PCKMO$")>;
1203
1204//===----------------------------------------------------------------------===//
1205// System: Miscellaneous Instructions
1206//===----------------------------------------------------------------------===//
1207
1208def : InstRW<[WLat30, MCD], (instregex "SVC$")>;
1209def : InstRW<[WLat1, FXU, GroupAlone], (instregex "MC$")>;
1210def : InstRW<[WLat30, MCD], (instregex "DIAG$")>;
1211def : InstRW<[WLat30, MCD], (instregex "TRAC(E|G)$")>;
1212def : InstRW<[WLat30, MCD], (instregex "TRAP(2|4)$")>;
1213def : InstRW<[WLat30, MCD], (instregex "SIG(P|A)$")>;
1214def : InstRW<[WLat30, MCD], (instregex "SIE$")>;
1215
1216//===----------------------------------------------------------------------===//
1217// System: CPU-Measurement Facility Instructions
1218//===----------------------------------------------------------------------===//
1219
1220def : InstRW<[WLat1, FXU, NormalGr], (instregex "LPP$")>;
1221def : InstRW<[WLat30, WLat30, MCD], (instregex "ECPGA$")>;
1222def : InstRW<[WLat30, WLat30, MCD], (instregex "E(C|P)CTR$")>;
1223def : InstRW<[WLat30, MCD], (instregex "LCCTL$")>;
1224def : InstRW<[WLat30, MCD], (instregex "L(P|S)CTL$")>;
1225def : InstRW<[WLat30, MCD], (instregex "Q(S|CTR)I$")>;
1226def : InstRW<[WLat30, MCD], (instregex "S(C|P)CTR$")>;
1227
1228//===----------------------------------------------------------------------===//
1229// System: I/O Instructions
1230//===----------------------------------------------------------------------===//
1231
1232def : InstRW<[WLat30, MCD], (instregex "(C|H|R|X)SCH$")>;
1233def : InstRW<[WLat30, MCD], (instregex "(M|S|ST|T)SCH$")>;
1234def : InstRW<[WLat30, MCD], (instregex "RCHP$")>;
1235def : InstRW<[WLat30, MCD], (instregex "SCHM$")>;
1236def : InstRW<[WLat30, MCD], (instregex "STC(PS|RW)$")>;
1237def : InstRW<[WLat30, MCD], (instregex "TPI$")>;
1238def : InstRW<[WLat30, MCD], (instregex "SAL$")>;
1239
1240}
1241
1242