• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1 //===- HexagonMCDuplexInfo.cpp - Instruction bundle checking --------------===//
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 implements duplexing of instructions to reduce code size
11 //
12 //===----------------------------------------------------------------------===//
13 
14 #include "MCTargetDesc/HexagonBaseInfo.h"
15 #include "MCTargetDesc/HexagonMCInstrInfo.h"
16 #include "MCTargetDesc/HexagonMCTargetDesc.h"
17 #include "llvm/ADT/SmallVector.h"
18 #include "llvm/MC/MCExpr.h"
19 #include "llvm/MC/MCInst.h"
20 #include "llvm/MC/MCSubtargetInfo.h"
21 #include "llvm/Support/Debug.h"
22 #include "llvm/Support/ErrorHandling.h"
23 #include "llvm/Support/MathExtras.h"
24 #include "llvm/Support/raw_ostream.h"
25 #include <cassert>
26 #include <cstdint>
27 #include <iterator>
28 #include <map>
29 #include <utility>
30 
31 using namespace llvm;
32 using namespace Hexagon;
33 
34 #define DEBUG_TYPE "hexagon-mcduplex-info"
35 
36 // pair table of subInstructions with opcodes
37 static const std::pair<unsigned, unsigned> opcodeData[] = {
38     std::make_pair((unsigned)SA1_addi, 0),
39     std::make_pair((unsigned)SA1_addrx, 6144),
40     std::make_pair((unsigned)SA1_addsp, 3072),
41     std::make_pair((unsigned)SA1_and1, 4608),
42     std::make_pair((unsigned)SA1_clrf, 6768),
43     std::make_pair((unsigned)SA1_clrfnew, 6736),
44     std::make_pair((unsigned)SA1_clrt, 6752),
45     std::make_pair((unsigned)SA1_clrtnew, 6720),
46     std::make_pair((unsigned)SA1_cmpeqi, 6400),
47     std::make_pair((unsigned)SA1_combine0i, 7168),
48     std::make_pair((unsigned)SA1_combine1i, 7176),
49     std::make_pair((unsigned)SA1_combine2i, 7184),
50     std::make_pair((unsigned)SA1_combine3i, 7192),
51     std::make_pair((unsigned)SA1_combinerz, 7432),
52     std::make_pair((unsigned)SA1_combinezr, 7424),
53     std::make_pair((unsigned)SA1_dec, 4864),
54     std::make_pair((unsigned)SA1_inc, 4352),
55     std::make_pair((unsigned)SA1_seti, 2048),
56     std::make_pair((unsigned)SA1_setin1, 6656),
57     std::make_pair((unsigned)SA1_sxtb, 5376),
58     std::make_pair((unsigned)SA1_sxth, 5120),
59     std::make_pair((unsigned)SA1_tfr, 4096),
60     std::make_pair((unsigned)SA1_zxtb, 5888),
61     std::make_pair((unsigned)SA1_zxth, 5632),
62     std::make_pair((unsigned)SL1_loadri_io, 0),
63     std::make_pair((unsigned)SL1_loadrub_io, 4096),
64     std::make_pair((unsigned)SL2_deallocframe, 7936),
65     std::make_pair((unsigned)SL2_jumpr31, 8128),
66     std::make_pair((unsigned)SL2_jumpr31_f, 8133),
67     std::make_pair((unsigned)SL2_jumpr31_fnew, 8135),
68     std::make_pair((unsigned)SL2_jumpr31_t, 8132),
69     std::make_pair((unsigned)SL2_jumpr31_tnew, 8134),
70     std::make_pair((unsigned)SL2_loadrb_io, 4096),
71     std::make_pair((unsigned)SL2_loadrd_sp, 7680),
72     std::make_pair((unsigned)SL2_loadrh_io, 0),
73     std::make_pair((unsigned)SL2_loadri_sp, 7168),
74     std::make_pair((unsigned)SL2_loadruh_io, 2048),
75     std::make_pair((unsigned)SL2_return, 8000),
76     std::make_pair((unsigned)SL2_return_f, 8005),
77     std::make_pair((unsigned)SL2_return_fnew, 8007),
78     std::make_pair((unsigned)SL2_return_t, 8004),
79     std::make_pair((unsigned)SL2_return_tnew, 8006),
80     std::make_pair((unsigned)SS1_storeb_io, 4096),
81     std::make_pair((unsigned)SS1_storew_io, 0),
82     std::make_pair((unsigned)SS2_allocframe, 7168),
83     std::make_pair((unsigned)SS2_storebi0, 4608),
84     std::make_pair((unsigned)SS2_storebi1, 4864),
85     std::make_pair((unsigned)SS2_stored_sp, 2560),
86     std::make_pair((unsigned)SS2_storeh_io, 0),
87     std::make_pair((unsigned)SS2_storew_sp, 2048),
88     std::make_pair((unsigned)SS2_storewi0, 4096),
89     std::make_pair((unsigned)SS2_storewi1, 4352)};
90 
isDuplexPairMatch(unsigned Ga,unsigned Gb)91 bool HexagonMCInstrInfo::isDuplexPairMatch(unsigned Ga, unsigned Gb) {
92   switch (Ga) {
93   case HexagonII::HSIG_None:
94   default:
95     return false;
96   case HexagonII::HSIG_L1:
97     return (Gb == HexagonII::HSIG_L1 || Gb == HexagonII::HSIG_A);
98   case HexagonII::HSIG_L2:
99     return (Gb == HexagonII::HSIG_L1 || Gb == HexagonII::HSIG_L2 ||
100             Gb == HexagonII::HSIG_A);
101   case HexagonII::HSIG_S1:
102     return (Gb == HexagonII::HSIG_L1 || Gb == HexagonII::HSIG_L2 ||
103             Gb == HexagonII::HSIG_S1 || Gb == HexagonII::HSIG_A);
104   case HexagonII::HSIG_S2:
105     return (Gb == HexagonII::HSIG_L1 || Gb == HexagonII::HSIG_L2 ||
106             Gb == HexagonII::HSIG_S1 || Gb == HexagonII::HSIG_S2 ||
107             Gb == HexagonII::HSIG_A);
108   case HexagonII::HSIG_A:
109     return (Gb == HexagonII::HSIG_A);
110   case HexagonII::HSIG_Compound:
111     return (Gb == HexagonII::HSIG_Compound);
112   }
113   return false;
114 }
115 
iClassOfDuplexPair(unsigned Ga,unsigned Gb)116 unsigned HexagonMCInstrInfo::iClassOfDuplexPair(unsigned Ga, unsigned Gb) {
117   switch (Ga) {
118   case HexagonII::HSIG_None:
119   default:
120     break;
121   case HexagonII::HSIG_L1:
122     switch (Gb) {
123     default:
124       break;
125     case HexagonII::HSIG_L1:
126       return 0;
127     case HexagonII::HSIG_A:
128       return 0x4;
129     }
130   case HexagonII::HSIG_L2:
131     switch (Gb) {
132     default:
133       break;
134     case HexagonII::HSIG_L1:
135       return 0x1;
136     case HexagonII::HSIG_L2:
137       return 0x2;
138     case HexagonII::HSIG_A:
139       return 0x5;
140     }
141   case HexagonII::HSIG_S1:
142     switch (Gb) {
143     default:
144       break;
145     case HexagonII::HSIG_L1:
146       return 0x8;
147     case HexagonII::HSIG_L2:
148       return 0x9;
149     case HexagonII::HSIG_S1:
150       return 0xA;
151     case HexagonII::HSIG_A:
152       return 0x6;
153     }
154   case HexagonII::HSIG_S2:
155     switch (Gb) {
156     default:
157       break;
158     case HexagonII::HSIG_L1:
159       return 0xC;
160     case HexagonII::HSIG_L2:
161       return 0xD;
162     case HexagonII::HSIG_S1:
163       return 0xB;
164     case HexagonII::HSIG_S2:
165       return 0xE;
166     case HexagonII::HSIG_A:
167       return 0x7;
168     }
169   case HexagonII::HSIG_A:
170     switch (Gb) {
171     default:
172       break;
173     case HexagonII::HSIG_A:
174       return 0x3;
175     }
176   case HexagonII::HSIG_Compound:
177     switch (Gb) {
178     case HexagonII::HSIG_Compound:
179       return 0xFFFFFFFF;
180     }
181   }
182   return 0xFFFFFFFF;
183 }
184 
getDuplexCandidateGroup(MCInst const & MCI)185 unsigned HexagonMCInstrInfo::getDuplexCandidateGroup(MCInst const &MCI) {
186   unsigned DstReg, PredReg, SrcReg, Src1Reg, Src2Reg;
187 
188   switch (MCI.getOpcode()) {
189   default:
190     return HexagonII::HSIG_None;
191   //
192   // Group L1:
193   //
194   // Rd = memw(Rs+#u4:2)
195   // Rd = memub(Rs+#u4:0)
196   case Hexagon::L2_loadri_io:
197     DstReg = MCI.getOperand(0).getReg();
198     SrcReg = MCI.getOperand(1).getReg();
199     // Special case this one from Group L2.
200     // Rd = memw(r29+#u5:2)
201     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg)) {
202       if (HexagonMCInstrInfo::isIntReg(SrcReg) &&
203           Hexagon::R29 == SrcReg && inRange<5, 2>(MCI, 2)) {
204         return HexagonII::HSIG_L2;
205       }
206       // Rd = memw(Rs+#u4:2)
207       if (HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
208           inRange<4, 2>(MCI, 2)) {
209         return HexagonII::HSIG_L1;
210       }
211     }
212     break;
213   case Hexagon::L2_loadrub_io:
214     // Rd = memub(Rs+#u4:0)
215     DstReg = MCI.getOperand(0).getReg();
216     SrcReg = MCI.getOperand(1).getReg();
217     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) &&
218         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
219         inRange<4>(MCI, 2)) {
220       return HexagonII::HSIG_L1;
221     }
222     break;
223   //
224   // Group L2:
225   //
226   // Rd = memh/memuh(Rs+#u3:1)
227   // Rd = memb(Rs+#u3:0)
228   // Rd = memw(r29+#u5:2) - Handled above.
229   // Rdd = memd(r29+#u5:3)
230   // deallocframe
231   // [if ([!]p0[.new])] dealloc_return
232   // [if ([!]p0[.new])] jumpr r31
233   case Hexagon::L2_loadrh_io:
234   case Hexagon::L2_loadruh_io:
235     // Rd = memh/memuh(Rs+#u3:1)
236     DstReg = MCI.getOperand(0).getReg();
237     SrcReg = MCI.getOperand(1).getReg();
238     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) &&
239         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
240         inRange<3, 1>(MCI, 2)) {
241       return HexagonII::HSIG_L2;
242     }
243     break;
244   case Hexagon::L2_loadrb_io:
245     // Rd = memb(Rs+#u3:0)
246     DstReg = MCI.getOperand(0).getReg();
247     SrcReg = MCI.getOperand(1).getReg();
248     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) &&
249         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
250         inRange<3>(MCI, 2)) {
251       return HexagonII::HSIG_L2;
252     }
253     break;
254   case Hexagon::L2_loadrd_io:
255     // Rdd = memd(r29+#u5:3)
256     DstReg = MCI.getOperand(0).getReg();
257     SrcReg = MCI.getOperand(1).getReg();
258     if (HexagonMCInstrInfo::isDblRegForSubInst(DstReg) &&
259         HexagonMCInstrInfo::isIntReg(SrcReg) && Hexagon::R29 == SrcReg &&
260         inRange<5, 3>(MCI, 2)) {
261       return HexagonII::HSIG_L2;
262     }
263     break;
264 
265   case Hexagon::L4_return:
266   case Hexagon::L2_deallocframe:
267     return HexagonII::HSIG_L2;
268 
269   case Hexagon::EH_RETURN_JMPR:
270   case Hexagon::J2_jumpr:
271   case Hexagon::PS_jmpret:
272     // jumpr r31
273     // Actual form JMPR implicit-def %pc, implicit %r31, implicit internal %r0.
274     DstReg = MCI.getOperand(0).getReg();
275     if (Hexagon::R31 == DstReg)
276       return HexagonII::HSIG_L2;
277     break;
278 
279   case Hexagon::J2_jumprt:
280   case Hexagon::J2_jumprf:
281   case Hexagon::J2_jumprtnew:
282   case Hexagon::J2_jumprfnew:
283   case Hexagon::J2_jumprtnewpt:
284   case Hexagon::J2_jumprfnewpt:
285   case Hexagon::PS_jmprett:
286   case Hexagon::PS_jmpretf:
287   case Hexagon::PS_jmprettnew:
288   case Hexagon::PS_jmpretfnew:
289   case Hexagon::PS_jmprettnewpt:
290   case Hexagon::PS_jmpretfnewpt:
291     DstReg = MCI.getOperand(1).getReg();
292     SrcReg = MCI.getOperand(0).getReg();
293     // [if ([!]p0[.new])] jumpr r31
294     if ((HexagonMCInstrInfo::isPredReg(SrcReg) && (Hexagon::P0 == SrcReg)) &&
295         (Hexagon::R31 == DstReg)) {
296       return HexagonII::HSIG_L2;
297     }
298     break;
299   case Hexagon::L4_return_t:
300   case Hexagon::L4_return_f:
301   case Hexagon::L4_return_tnew_pnt:
302   case Hexagon::L4_return_fnew_pnt:
303   case Hexagon::L4_return_tnew_pt:
304   case Hexagon::L4_return_fnew_pt:
305     // [if ([!]p0[.new])] dealloc_return
306     SrcReg = MCI.getOperand(1).getReg();
307     if (Hexagon::P0 == SrcReg) {
308       return HexagonII::HSIG_L2;
309     }
310     break;
311   //
312   // Group S1:
313   //
314   // memw(Rs+#u4:2) = Rt
315   // memb(Rs+#u4:0) = Rt
316   case Hexagon::S2_storeri_io:
317     // Special case this one from Group S2.
318     // memw(r29+#u5:2) = Rt
319     Src1Reg = MCI.getOperand(0).getReg();
320     Src2Reg = MCI.getOperand(2).getReg();
321     if (HexagonMCInstrInfo::isIntReg(Src1Reg) &&
322         HexagonMCInstrInfo::isIntRegForSubInst(Src2Reg) &&
323         Hexagon::R29 == Src1Reg && inRange<5, 2>(MCI, 1)) {
324       return HexagonII::HSIG_S2;
325     }
326     // memw(Rs+#u4:2) = Rt
327     if (HexagonMCInstrInfo::isIntRegForSubInst(Src1Reg) &&
328         HexagonMCInstrInfo::isIntRegForSubInst(Src2Reg) &&
329         inRange<4, 2>(MCI, 1)) {
330       return HexagonII::HSIG_S1;
331     }
332     break;
333   case Hexagon::S2_storerb_io:
334     // memb(Rs+#u4:0) = Rt
335     Src1Reg = MCI.getOperand(0).getReg();
336     Src2Reg = MCI.getOperand(2).getReg();
337     if (HexagonMCInstrInfo::isIntRegForSubInst(Src1Reg) &&
338         HexagonMCInstrInfo::isIntRegForSubInst(Src2Reg) &&
339         inRange<4>(MCI, 1)) {
340       return HexagonII::HSIG_S1;
341     }
342     break;
343   //
344   // Group S2:
345   //
346   // memh(Rs+#u3:1) = Rt
347   // memw(r29+#u5:2) = Rt
348   // memd(r29+#s6:3) = Rtt
349   // memw(Rs+#u4:2) = #U1
350   // memb(Rs+#u4) = #U1
351   // allocframe(#u5:3)
352   case Hexagon::S2_storerh_io:
353     // memh(Rs+#u3:1) = Rt
354     Src1Reg = MCI.getOperand(0).getReg();
355     Src2Reg = MCI.getOperand(2).getReg();
356     if (HexagonMCInstrInfo::isIntRegForSubInst(Src1Reg) &&
357         HexagonMCInstrInfo::isIntRegForSubInst(Src2Reg) &&
358         inRange<3, 1>(MCI, 1)) {
359       return HexagonII::HSIG_S2;
360     }
361     break;
362   case Hexagon::S2_storerd_io:
363     // memd(r29+#s6:3) = Rtt
364     Src1Reg = MCI.getOperand(0).getReg();
365     Src2Reg = MCI.getOperand(2).getReg();
366     if (HexagonMCInstrInfo::isDblRegForSubInst(Src2Reg) &&
367         HexagonMCInstrInfo::isIntReg(Src1Reg) && Hexagon::R29 == Src1Reg &&
368         inSRange<6, 3>(MCI, 1)) {
369       return HexagonII::HSIG_S2;
370     }
371     break;
372   case Hexagon::S4_storeiri_io:
373     // memw(Rs+#u4:2) = #U1
374     Src1Reg = MCI.getOperand(0).getReg();
375     if (HexagonMCInstrInfo::isIntRegForSubInst(Src1Reg) &&
376         inRange<4, 2>(MCI, 1) && inRange<1>(MCI, 2)) {
377       return HexagonII::HSIG_S2;
378     }
379     break;
380   case Hexagon::S4_storeirb_io:
381     // memb(Rs+#u4) = #U1
382     Src1Reg = MCI.getOperand(0).getReg();
383     if (HexagonMCInstrInfo::isIntRegForSubInst(Src1Reg) &&
384         inRange<4>(MCI, 1) && inRange<1>(MCI, 2)) {
385       return HexagonII::HSIG_S2;
386     }
387     break;
388   case Hexagon::S2_allocframe:
389     if (inRange<5, 3>(MCI, 2))
390       return HexagonII::HSIG_S2;
391     break;
392   //
393   // Group A:
394   //
395   // Rx = add(Rx,#s7)
396   // Rd = Rs
397   // Rd = #u6
398   // Rd = #-1
399   // if ([!]P0[.new]) Rd = #0
400   // Rd = add(r29,#u6:2)
401   // Rx = add(Rx,Rs)
402   // P0 = cmp.eq(Rs,#u2)
403   // Rdd = combine(#0,Rs)
404   // Rdd = combine(Rs,#0)
405   // Rdd = combine(#u2,#U2)
406   // Rd = add(Rs,#1)
407   // Rd = add(Rs,#-1)
408   // Rd = sxth/sxtb/zxtb/zxth(Rs)
409   // Rd = and(Rs,#1)
410   case Hexagon::A2_addi:
411     DstReg = MCI.getOperand(0).getReg();
412     SrcReg = MCI.getOperand(1).getReg();
413     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg)) {
414       // Rd = add(r29,#u6:2)
415       if (HexagonMCInstrInfo::isIntReg(SrcReg) && Hexagon::R29 == SrcReg &&
416           inRange<6, 2>(MCI, 2)) {
417         return HexagonII::HSIG_A;
418       }
419       // Rx = add(Rx,#s7)
420       if (DstReg == SrcReg) {
421         return HexagonII::HSIG_A;
422       }
423       // Rd = add(Rs,#1)
424       // Rd = add(Rs,#-1)
425       if (HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
426           (minConstant(MCI, 2) == 1 || minConstant(MCI, 2) == -1)) {
427         return HexagonII::HSIG_A;
428       }
429     }
430     break;
431   case Hexagon::A2_add:
432     // Rx = add(Rx,Rs)
433     DstReg = MCI.getOperand(0).getReg();
434     Src1Reg = MCI.getOperand(1).getReg();
435     Src2Reg = MCI.getOperand(2).getReg();
436     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) && (DstReg == Src1Reg) &&
437         HexagonMCInstrInfo::isIntRegForSubInst(Src2Reg)) {
438       return HexagonII::HSIG_A;
439     }
440     break;
441   case Hexagon::A2_andir:
442     DstReg = MCI.getOperand(0).getReg();
443     SrcReg = MCI.getOperand(1).getReg();
444     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) &&
445         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
446         (minConstant(MCI, 2) == 1 || minConstant(MCI, 2) == 255)) {
447       return HexagonII::HSIG_A;
448     }
449     break;
450   case Hexagon::A2_tfr:
451     // Rd = Rs
452     DstReg = MCI.getOperand(0).getReg();
453     SrcReg = MCI.getOperand(1).getReg();
454     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) &&
455         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg)) {
456       return HexagonII::HSIG_A;
457     }
458     break;
459   case Hexagon::A2_tfrsi:
460     DstReg = MCI.getOperand(0).getReg();
461 
462     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg)) {
463       return HexagonII::HSIG_A;
464     }
465     break;
466   case Hexagon::C2_cmoveit:
467   case Hexagon::C2_cmovenewit:
468   case Hexagon::C2_cmoveif:
469   case Hexagon::C2_cmovenewif:
470     // if ([!]P0[.new]) Rd = #0
471     // Actual form:
472     // %r16 = C2_cmovenewit internal %p0, 0, implicit undef %r16;
473     DstReg = MCI.getOperand(0).getReg();  // Rd
474     PredReg = MCI.getOperand(1).getReg(); // P0
475     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) &&
476         Hexagon::P0 == PredReg && minConstant(MCI, 2) == 0) {
477       return HexagonII::HSIG_A;
478     }
479     break;
480   case Hexagon::C2_cmpeqi:
481     // P0 = cmp.eq(Rs,#u2)
482     DstReg = MCI.getOperand(0).getReg();
483     SrcReg = MCI.getOperand(1).getReg();
484     if (Hexagon::P0 == DstReg &&
485         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
486         inRange<2>(MCI, 2)) {
487       return HexagonII::HSIG_A;
488     }
489     break;
490   case Hexagon::A2_combineii:
491   case Hexagon::A4_combineii:
492     // Rdd = combine(#u2,#U2)
493     DstReg = MCI.getOperand(0).getReg();
494     if (HexagonMCInstrInfo::isDblRegForSubInst(DstReg) &&
495         inRange<2>(MCI, 1) && inRange<2>(MCI, 2)) {
496       return HexagonII::HSIG_A;
497     }
498     break;
499   case Hexagon::A4_combineri:
500     // Rdd = combine(Rs,#0)
501     DstReg = MCI.getOperand(0).getReg();
502     SrcReg = MCI.getOperand(1).getReg();
503     if (HexagonMCInstrInfo::isDblRegForSubInst(DstReg) &&
504         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
505         minConstant(MCI, 2) == 0) {
506       return HexagonII::HSIG_A;
507     }
508     break;
509   case Hexagon::A4_combineir:
510     // Rdd = combine(#0,Rs)
511     DstReg = MCI.getOperand(0).getReg();
512     SrcReg = MCI.getOperand(2).getReg();
513     if (HexagonMCInstrInfo::isDblRegForSubInst(DstReg) &&
514         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg) &&
515         minConstant(MCI, 1) == 0) {
516       return HexagonII::HSIG_A;
517     }
518     break;
519   case Hexagon::A2_sxtb:
520   case Hexagon::A2_sxth:
521   case Hexagon::A2_zxtb:
522   case Hexagon::A2_zxth:
523     // Rd = sxth/sxtb/zxtb/zxth(Rs)
524     DstReg = MCI.getOperand(0).getReg();
525     SrcReg = MCI.getOperand(1).getReg();
526     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg) &&
527         HexagonMCInstrInfo::isIntRegForSubInst(SrcReg)) {
528       return HexagonII::HSIG_A;
529     }
530     break;
531   }
532 
533   return HexagonII::HSIG_None;
534 }
535 
subInstWouldBeExtended(MCInst const & potentialDuplex)536 bool HexagonMCInstrInfo::subInstWouldBeExtended(MCInst const &potentialDuplex) {
537   unsigned DstReg, SrcReg;
538   switch (potentialDuplex.getOpcode()) {
539   case Hexagon::A2_addi:
540     // testing for case of: Rx = add(Rx,#s7)
541     DstReg = potentialDuplex.getOperand(0).getReg();
542     SrcReg = potentialDuplex.getOperand(1).getReg();
543     if (DstReg == SrcReg && HexagonMCInstrInfo::isIntRegForSubInst(DstReg)) {
544       int64_t Value;
545       if (!potentialDuplex.getOperand(2).getExpr()->evaluateAsAbsolute(Value))
546         return true;
547       if (!isShiftedInt<7, 0>(Value))
548         return true;
549     }
550     break;
551   case Hexagon::A2_tfrsi:
552     DstReg = potentialDuplex.getOperand(0).getReg();
553 
554     if (HexagonMCInstrInfo::isIntRegForSubInst(DstReg)) {
555       int64_t Value;
556       if (!potentialDuplex.getOperand(1).getExpr()->evaluateAsAbsolute(Value))
557         return true;
558       // Check for case of Rd = #-1.
559       if (Value == -1)
560         return false;
561       // Check for case of Rd = #u6.
562       if (!isShiftedUInt<6, 0>(Value))
563         return true;
564     }
565     break;
566   default:
567     break;
568   }
569   return false;
570 }
571 
572 /// non-Symmetrical. See if these two instructions are fit for duplex pair.
isOrderedDuplexPair(MCInstrInfo const & MCII,MCInst const & MIa,bool ExtendedA,MCInst const & MIb,bool ExtendedB,bool bisReversable,MCSubtargetInfo const & STI)573 bool HexagonMCInstrInfo::isOrderedDuplexPair(MCInstrInfo const &MCII,
574                                              MCInst const &MIa, bool ExtendedA,
575                                              MCInst const &MIb, bool ExtendedB,
576                                              bool bisReversable,
577                                              MCSubtargetInfo const &STI) {
578   // Slot 1 cannot be extended in duplexes PRM 10.5
579   if (ExtendedA)
580     return false;
581   // Only A2_addi and A2_tfrsi can be extended in duplex form PRM 10.5
582   if (ExtendedB) {
583     unsigned Opcode = MIb.getOpcode();
584     if ((Opcode != Hexagon::A2_addi) && (Opcode != Hexagon::A2_tfrsi))
585       return false;
586   }
587   unsigned MIaG = HexagonMCInstrInfo::getDuplexCandidateGroup(MIa),
588            MIbG = HexagonMCInstrInfo::getDuplexCandidateGroup(MIb);
589 
590   static std::map<unsigned, unsigned> subinstOpcodeMap(std::begin(opcodeData),
591                                                        std::end(opcodeData));
592 
593   // If a duplex contains 2 insns in the same group, the insns must be
594   // ordered such that the numerically smaller opcode is in slot 1.
595   if ((MIaG != HexagonII::HSIG_None) && (MIaG == MIbG) && bisReversable) {
596     MCInst SubInst0 = HexagonMCInstrInfo::deriveSubInst(MIa);
597     MCInst SubInst1 = HexagonMCInstrInfo::deriveSubInst(MIb);
598 
599     unsigned zeroedSubInstS0 =
600         subinstOpcodeMap.find(SubInst0.getOpcode())->second;
601     unsigned zeroedSubInstS1 =
602         subinstOpcodeMap.find(SubInst1.getOpcode())->second;
603 
604     if (zeroedSubInstS0 < zeroedSubInstS1)
605       // subinstS0 (maps to slot 0) must be greater than
606       // subinstS1 (maps to slot 1)
607       return false;
608   }
609 
610   // allocframe must always be in slot 0
611   if (MIb.getOpcode() == Hexagon::S2_allocframe)
612     return false;
613 
614   if ((MIaG != HexagonII::HSIG_None) && (MIbG != HexagonII::HSIG_None)) {
615     // Prevent 2 instructions with extenders from duplexing
616     // Note that MIb (slot1) can be extended and MIa (slot0)
617     //   can never be extended
618     if (subInstWouldBeExtended(MIa))
619       return false;
620 
621     // If duplexing produces an extender, but the original did not
622     //   have an extender, do not duplex.
623     if (subInstWouldBeExtended(MIb) && !ExtendedB)
624       return false;
625   }
626 
627   // If jumpr r31 appears, it must be in slot 0, and never slot 1 (MIb).
628   if (MIbG == HexagonII::HSIG_L2) {
629     if ((MIb.getNumOperands() > 1) && MIb.getOperand(1).isReg() &&
630         (MIb.getOperand(1).getReg() == Hexagon::R31))
631       return false;
632     if ((MIb.getNumOperands() > 0) && MIb.getOperand(0).isReg() &&
633         (MIb.getOperand(0).getReg() == Hexagon::R31))
634       return false;
635   }
636 
637   if (STI.getCPU().equals_lower("hexagonv4") ||
638       STI.getCPU().equals_lower("hexagonv5") ||
639       STI.getCPU().equals_lower("hexagonv55") ||
640       STI.getCPU().equals_lower("hexagonv60")) {
641     // If a store appears, it must be in slot 0 (MIa) 1st, and then slot 1 (MIb);
642     //   therefore, not duplexable if slot 1 is a store, and slot 0 is not.
643     if ((MIbG == HexagonII::HSIG_S1) || (MIbG == HexagonII::HSIG_S2)) {
644       if ((MIaG != HexagonII::HSIG_S1) && (MIaG != HexagonII::HSIG_S2))
645         return false;
646     }
647   }
648 
649   return (isDuplexPairMatch(MIaG, MIbG));
650 }
651 
652 /// Symmetrical. See if these two instructions are fit for duplex pair.
isDuplexPair(MCInst const & MIa,MCInst const & MIb)653 bool HexagonMCInstrInfo::isDuplexPair(MCInst const &MIa, MCInst const &MIb) {
654   unsigned MIaG = getDuplexCandidateGroup(MIa),
655            MIbG = getDuplexCandidateGroup(MIb);
656   return (isDuplexPairMatch(MIaG, MIbG) || isDuplexPairMatch(MIbG, MIaG));
657 }
658 
addOps(MCInst & subInstPtr,MCInst const & Inst,unsigned opNum)659 inline static void addOps(MCInst &subInstPtr, MCInst const &Inst,
660                           unsigned opNum) {
661   if (Inst.getOperand(opNum).isReg()) {
662     switch (Inst.getOperand(opNum).getReg()) {
663     default:
664       llvm_unreachable("Not Duplexable Register");
665       break;
666     case Hexagon::R0:
667     case Hexagon::R1:
668     case Hexagon::R2:
669     case Hexagon::R3:
670     case Hexagon::R4:
671     case Hexagon::R5:
672     case Hexagon::R6:
673     case Hexagon::R7:
674     case Hexagon::D0:
675     case Hexagon::D1:
676     case Hexagon::D2:
677     case Hexagon::D3:
678     case Hexagon::R16:
679     case Hexagon::R17:
680     case Hexagon::R18:
681     case Hexagon::R19:
682     case Hexagon::R20:
683     case Hexagon::R21:
684     case Hexagon::R22:
685     case Hexagon::R23:
686     case Hexagon::D8:
687     case Hexagon::D9:
688     case Hexagon::D10:
689     case Hexagon::D11:
690     case Hexagon::P0:
691       subInstPtr.addOperand(Inst.getOperand(opNum));
692       break;
693     }
694   } else
695     subInstPtr.addOperand(Inst.getOperand(opNum));
696 }
697 
deriveSubInst(MCInst const & Inst)698 MCInst HexagonMCInstrInfo::deriveSubInst(MCInst const &Inst) {
699   MCInst Result;
700   bool Absolute;
701   int64_t Value;
702   switch (Inst.getOpcode()) {
703   default:
704     // dbgs() << "opcode: "<< Inst->getOpcode() << "\n";
705     llvm_unreachable("Unimplemented subinstruction \n");
706     break;
707   case Hexagon::A2_addi:
708     Absolute = Inst.getOperand(2).getExpr()->evaluateAsAbsolute(Value);
709     if (Absolute) {
710       if (Value == 1) {
711         Result.setOpcode(Hexagon::SA1_inc);
712         addOps(Result, Inst, 0);
713         addOps(Result, Inst, 1);
714         break;
715       } //  1,2 SUBInst $Rd = add($Rs, #1)
716       if (Value == -1) {
717         Result.setOpcode(Hexagon::SA1_dec);
718         addOps(Result, Inst, 0);
719         addOps(Result, Inst, 1);
720         addOps(Result, Inst, 2);
721         break;
722       } //  1,2 SUBInst $Rd = add($Rs,#-1)
723       if (Inst.getOperand(1).getReg() == Hexagon::R29) {
724         Result.setOpcode(Hexagon::SA1_addsp);
725         addOps(Result, Inst, 0);
726         addOps(Result, Inst, 2);
727         break;
728       } //  1,3 SUBInst $Rd = add(r29, #$u6_2)
729     }
730     Result.setOpcode(Hexagon::SA1_addi);
731     addOps(Result, Inst, 0);
732     addOps(Result, Inst, 1);
733     addOps(Result, Inst, 2);
734     break; //    1,2,3 SUBInst $Rx = add($Rx, #$s7)
735   case Hexagon::A2_add:
736     Result.setOpcode(Hexagon::SA1_addrx);
737     addOps(Result, Inst, 0);
738     addOps(Result, Inst, 1);
739     addOps(Result, Inst, 2);
740     break; //    1,2,3 SUBInst $Rx = add($_src_, $Rs)
741   case Hexagon::S2_allocframe:
742     Result.setOpcode(Hexagon::SS2_allocframe);
743     addOps(Result, Inst, 2);
744     break; //    1 SUBInst allocframe(#$u5_3)
745   case Hexagon::A2_andir:
746     if (minConstant(Inst, 2) == 255) {
747       Result.setOpcode(Hexagon::SA1_zxtb);
748       addOps(Result, Inst, 0);
749       addOps(Result, Inst, 1);
750       break; //    1,2    $Rd = and($Rs, #255)
751     } else {
752       Result.setOpcode(Hexagon::SA1_and1);
753       addOps(Result, Inst, 0);
754       addOps(Result, Inst, 1);
755       break; //    1,2 SUBInst $Rd = and($Rs, #1)
756     }
757   case Hexagon::C2_cmpeqi:
758     Result.setOpcode(Hexagon::SA1_cmpeqi);
759     addOps(Result, Inst, 1);
760     addOps(Result, Inst, 2);
761     break; //    2,3 SUBInst p0 = cmp.eq($Rs, #$u2)
762   case Hexagon::A4_combineii:
763   case Hexagon::A2_combineii:
764     Absolute = Inst.getOperand(1).getExpr()->evaluateAsAbsolute(Value);
765     assert(Absolute);(void)Absolute;
766     if (Value == 1) {
767       Result.setOpcode(Hexagon::SA1_combine1i);
768       addOps(Result, Inst, 0);
769       addOps(Result, Inst, 2);
770       break; //  1,3 SUBInst $Rdd = combine(#1, #$u2)
771     }
772     if (Value == 3) {
773       Result.setOpcode(Hexagon::SA1_combine3i);
774       addOps(Result, Inst, 0);
775       addOps(Result, Inst, 2);
776       break; //  1,3 SUBInst $Rdd = combine(#3, #$u2)
777     }
778     if (Value == 0) {
779       Result.setOpcode(Hexagon::SA1_combine0i);
780       addOps(Result, Inst, 0);
781       addOps(Result, Inst, 2);
782       break; //  1,3 SUBInst $Rdd = combine(#0, #$u2)
783     }
784     if (Value == 2) {
785       Result.setOpcode(Hexagon::SA1_combine2i);
786       addOps(Result, Inst, 0);
787       addOps(Result, Inst, 2);
788       break; //  1,3 SUBInst $Rdd = combine(#2, #$u2)
789     }
790     break;
791   case Hexagon::A4_combineir:
792     Result.setOpcode(Hexagon::SA1_combinezr);
793     addOps(Result, Inst, 0);
794     addOps(Result, Inst, 2);
795     break; //    1,3 SUBInst $Rdd = combine(#0, $Rs)
796   case Hexagon::A4_combineri:
797     Result.setOpcode(Hexagon::SA1_combinerz);
798     addOps(Result, Inst, 0);
799     addOps(Result, Inst, 1);
800     break; //    1,2 SUBInst $Rdd = combine($Rs, #0)
801   case Hexagon::L4_return_tnew_pnt:
802   case Hexagon::L4_return_tnew_pt:
803     Result.setOpcode(Hexagon::SL2_return_tnew);
804     break; //    none  SUBInst if (p0.new) dealloc_return:nt
805   case Hexagon::L4_return_fnew_pnt:
806   case Hexagon::L4_return_fnew_pt:
807     Result.setOpcode(Hexagon::SL2_return_fnew);
808     break; //    none  SUBInst if (!p0.new) dealloc_return:nt
809   case Hexagon::L4_return_f:
810     Result.setOpcode(Hexagon::SL2_return_f);
811     break; //    none  SUBInst if (!p0) dealloc_return
812   case Hexagon::L4_return_t:
813     Result.setOpcode(Hexagon::SL2_return_t);
814     break; //    none  SUBInst if (p0) dealloc_return
815   case Hexagon::L4_return:
816     Result.setOpcode(Hexagon::SL2_return);
817     break; //    none  SUBInst dealloc_return
818   case Hexagon::L2_deallocframe:
819     Result.setOpcode(Hexagon::SL2_deallocframe);
820     break; //    none  SUBInst deallocframe
821   case Hexagon::EH_RETURN_JMPR:
822   case Hexagon::J2_jumpr:
823   case Hexagon::PS_jmpret:
824     Result.setOpcode(Hexagon::SL2_jumpr31);
825     break; //    none  SUBInst jumpr r31
826   case Hexagon::J2_jumprf:
827   case Hexagon::PS_jmpretf:
828     Result.setOpcode(Hexagon::SL2_jumpr31_f);
829     break; //    none  SUBInst if (!p0) jumpr r31
830   case Hexagon::J2_jumprfnew:
831   case Hexagon::J2_jumprfnewpt:
832   case Hexagon::PS_jmpretfnewpt:
833   case Hexagon::PS_jmpretfnew:
834     Result.setOpcode(Hexagon::SL2_jumpr31_fnew);
835     break; //    none  SUBInst if (!p0.new) jumpr:nt r31
836   case Hexagon::J2_jumprt:
837   case Hexagon::PS_jmprett:
838     Result.setOpcode(Hexagon::SL2_jumpr31_t);
839     break; //    none  SUBInst if (p0) jumpr r31
840   case Hexagon::J2_jumprtnew:
841   case Hexagon::J2_jumprtnewpt:
842   case Hexagon::PS_jmprettnewpt:
843   case Hexagon::PS_jmprettnew:
844     Result.setOpcode(Hexagon::SL2_jumpr31_tnew);
845     break; //    none  SUBInst if (p0.new) jumpr:nt r31
846   case Hexagon::L2_loadrb_io:
847     Result.setOpcode(Hexagon::SL2_loadrb_io);
848     addOps(Result, Inst, 0);
849     addOps(Result, Inst, 1);
850     addOps(Result, Inst, 2);
851     break; //    1,2,3 SUBInst $Rd = memb($Rs + #$u3_0)
852   case Hexagon::L2_loadrd_io:
853     Result.setOpcode(Hexagon::SL2_loadrd_sp);
854     addOps(Result, Inst, 0);
855     addOps(Result, Inst, 2);
856     break; //    1,3 SUBInst $Rdd = memd(r29 + #$u5_3)
857   case Hexagon::L2_loadrh_io:
858     Result.setOpcode(Hexagon::SL2_loadrh_io);
859     addOps(Result, Inst, 0);
860     addOps(Result, Inst, 1);
861     addOps(Result, Inst, 2);
862     break; //    1,2,3 SUBInst $Rd = memh($Rs + #$u3_1)
863   case Hexagon::L2_loadrub_io:
864     Result.setOpcode(Hexagon::SL1_loadrub_io);
865     addOps(Result, Inst, 0);
866     addOps(Result, Inst, 1);
867     addOps(Result, Inst, 2);
868     break; //    1,2,3 SUBInst $Rd = memub($Rs + #$u4_0)
869   case Hexagon::L2_loadruh_io:
870     Result.setOpcode(Hexagon::SL2_loadruh_io);
871     addOps(Result, Inst, 0);
872     addOps(Result, Inst, 1);
873     addOps(Result, Inst, 2);
874     break; //    1,2,3 SUBInst $Rd = memuh($Rs + #$u3_1)
875   case Hexagon::L2_loadri_io:
876     if (Inst.getOperand(1).getReg() == Hexagon::R29) {
877       Result.setOpcode(Hexagon::SL2_loadri_sp);
878       addOps(Result, Inst, 0);
879       addOps(Result, Inst, 2);
880       break; //  2 1,3 SUBInst $Rd = memw(r29 + #$u5_2)
881     } else {
882       Result.setOpcode(Hexagon::SL1_loadri_io);
883       addOps(Result, Inst, 0);
884       addOps(Result, Inst, 1);
885       addOps(Result, Inst, 2);
886       break; //    1,2,3 SUBInst $Rd = memw($Rs + #$u4_2)
887     }
888   case Hexagon::S4_storeirb_io:
889     Absolute = Inst.getOperand(2).getExpr()->evaluateAsAbsolute(Value);
890     assert(Absolute);(void)Absolute;
891     if (Value == 0) {
892       Result.setOpcode(Hexagon::SS2_storebi0);
893       addOps(Result, Inst, 0);
894       addOps(Result, Inst, 1);
895       break; //    1,2 SUBInst memb($Rs + #$u4_0)=#0
896     } else if (Value == 1) {
897       Result.setOpcode(Hexagon::SS2_storebi1);
898       addOps(Result, Inst, 0);
899       addOps(Result, Inst, 1);
900       break; //  2 1,2 SUBInst memb($Rs + #$u4_0)=#1
901     }
902     break;
903   case Hexagon::S2_storerb_io:
904     Result.setOpcode(Hexagon::SS1_storeb_io);
905     addOps(Result, Inst, 0);
906     addOps(Result, Inst, 1);
907     addOps(Result, Inst, 2);
908     break; //    1,2,3 SUBInst memb($Rs + #$u4_0) = $Rt
909   case Hexagon::S2_storerd_io:
910     Result.setOpcode(Hexagon::SS2_stored_sp);
911     addOps(Result, Inst, 1);
912     addOps(Result, Inst, 2);
913     break; //    2,3 SUBInst memd(r29 + #$s6_3) = $Rtt
914   case Hexagon::S2_storerh_io:
915     Result.setOpcode(Hexagon::SS2_storeh_io);
916     addOps(Result, Inst, 0);
917     addOps(Result, Inst, 1);
918     addOps(Result, Inst, 2);
919     break; //    1,2,3 SUBInst memb($Rs + #$u4_0) = $Rt
920   case Hexagon::S4_storeiri_io:
921     Absolute = Inst.getOperand(2).getExpr()->evaluateAsAbsolute(Value);
922     assert(Absolute);(void)Absolute;
923     if (Value == 0) {
924       Result.setOpcode(Hexagon::SS2_storewi0);
925       addOps(Result, Inst, 0);
926       addOps(Result, Inst, 1);
927       break; //  3 1,2 SUBInst memw($Rs + #$u4_2)=#0
928     } else if (Value == 1) {
929       Result.setOpcode(Hexagon::SS2_storewi1);
930       addOps(Result, Inst, 0);
931       addOps(Result, Inst, 1);
932       break; //  3 1,2 SUBInst memw($Rs + #$u4_2)=#1
933     } else if (Inst.getOperand(0).getReg() == Hexagon::R29) {
934       Result.setOpcode(Hexagon::SS2_storew_sp);
935       addOps(Result, Inst, 1);
936       addOps(Result, Inst, 2);
937       break; //  1 2,3 SUBInst memw(r29 + #$u5_2) = $Rt
938     }
939     break;
940   case Hexagon::S2_storeri_io:
941     if (Inst.getOperand(0).getReg() == Hexagon::R29) {
942       Result.setOpcode(Hexagon::SS2_storew_sp);
943       addOps(Result, Inst, 1);
944       addOps(Result, Inst, 2); //  1,2,3 SUBInst memw(sp + #$u5_2) = $Rt
945     } else {
946       Result.setOpcode(Hexagon::SS1_storew_io);
947       addOps(Result, Inst, 0);
948       addOps(Result, Inst, 1);
949       addOps(Result, Inst, 2); //  1,2,3 SUBInst memw($Rs + #$u4_2) = $Rt
950     }
951     break;
952   case Hexagon::A2_sxtb:
953     Result.setOpcode(Hexagon::SA1_sxtb);
954     addOps(Result, Inst, 0);
955     addOps(Result, Inst, 1);
956     break; //  1,2 SUBInst $Rd = sxtb($Rs)
957   case Hexagon::A2_sxth:
958     Result.setOpcode(Hexagon::SA1_sxth);
959     addOps(Result, Inst, 0);
960     addOps(Result, Inst, 1);
961     break; //  1,2 SUBInst $Rd = sxth($Rs)
962   case Hexagon::A2_tfr:
963     Result.setOpcode(Hexagon::SA1_tfr);
964     addOps(Result, Inst, 0);
965     addOps(Result, Inst, 1);
966     break; //  1,2 SUBInst $Rd = $Rs
967   case Hexagon::C2_cmovenewif:
968     Result.setOpcode(Hexagon::SA1_clrfnew);
969     addOps(Result, Inst, 0);
970     addOps(Result, Inst, 1);
971     break; //  2 SUBInst if (!p0.new) $Rd = #0
972   case Hexagon::C2_cmovenewit:
973     Result.setOpcode(Hexagon::SA1_clrtnew);
974     addOps(Result, Inst, 0);
975     addOps(Result, Inst, 1);
976     break; //  2 SUBInst if (p0.new) $Rd = #0
977   case Hexagon::C2_cmoveif:
978     Result.setOpcode(Hexagon::SA1_clrf);
979     addOps(Result, Inst, 0);
980     addOps(Result, Inst, 1);
981     break; //  2 SUBInst if (!p0) $Rd = #0
982   case Hexagon::C2_cmoveit:
983     Result.setOpcode(Hexagon::SA1_clrt);
984     addOps(Result, Inst, 0);
985     addOps(Result, Inst, 1);
986     break; //  2 SUBInst if (p0) $Rd = #0
987   case Hexagon::A2_tfrsi:
988     Absolute = Inst.getOperand(1).getExpr()->evaluateAsAbsolute(Value);
989     if (Absolute && Value == -1) {
990       Result.setOpcode(Hexagon::SA1_setin1);
991       addOps(Result, Inst, 0);
992       addOps(Result, Inst, 1);
993       break; //  2 1 SUBInst $Rd = #-1
994     } else {
995       Result.setOpcode(Hexagon::SA1_seti);
996       addOps(Result, Inst, 0);
997       addOps(Result, Inst, 1);
998       break; //    1,2 SUBInst $Rd = #$u6
999     }
1000   case Hexagon::A2_zxtb:
1001     Result.setOpcode(Hexagon::SA1_zxtb);
1002     addOps(Result, Inst, 0);
1003     addOps(Result, Inst, 1);
1004     break; //    1,2    $Rd = and($Rs, #255)
1005 
1006   case Hexagon::A2_zxth:
1007     Result.setOpcode(Hexagon::SA1_zxth);
1008     addOps(Result, Inst, 0);
1009     addOps(Result, Inst, 1);
1010     break; //    1,2 SUBInst $Rd = zxth($Rs)
1011   }
1012   return Result;
1013 }
1014 
isStoreInst(unsigned opCode)1015 static bool isStoreInst(unsigned opCode) {
1016   switch (opCode) {
1017   case Hexagon::S2_storeri_io:
1018   case Hexagon::S2_storerb_io:
1019   case Hexagon::S2_storerh_io:
1020   case Hexagon::S2_storerd_io:
1021   case Hexagon::S4_storeiri_io:
1022   case Hexagon::S4_storeirb_io:
1023   case Hexagon::S2_allocframe:
1024     return true;
1025   default:
1026     return false;
1027   }
1028 }
1029 
1030 SmallVector<DuplexCandidate, 8>
getDuplexPossibilties(MCInstrInfo const & MCII,MCSubtargetInfo const & STI,MCInst const & MCB)1031 HexagonMCInstrInfo::getDuplexPossibilties(MCInstrInfo const &MCII,
1032                                           MCSubtargetInfo const &STI,
1033                                           MCInst const &MCB) {
1034   assert(isBundle(MCB));
1035   SmallVector<DuplexCandidate, 8> duplexToTry;
1036   // Use an "order matters" version of isDuplexPair.
1037   unsigned numInstrInPacket = MCB.getNumOperands();
1038 
1039   for (unsigned distance = 1; distance < numInstrInPacket; ++distance) {
1040     for (unsigned j = HexagonMCInstrInfo::bundleInstructionsOffset,
1041                   k = j + distance;
1042          (j < numInstrInPacket) && (k < numInstrInPacket); ++j, ++k) {
1043 
1044       // Check if reversible.
1045       bool bisReversable = true;
1046       if (isStoreInst(MCB.getOperand(j).getInst()->getOpcode()) &&
1047           isStoreInst(MCB.getOperand(k).getInst()->getOpcode())) {
1048         LLVM_DEBUG(dbgs() << "skip out of order write pair: " << k << "," << j
1049                           << "\n");
1050         bisReversable = false;
1051       }
1052       if (HexagonMCInstrInfo::isMemReorderDisabled(MCB)) // }:mem_noshuf
1053         bisReversable = false;
1054 
1055       // Try in order.
1056       if (isOrderedDuplexPair(
1057               MCII, *MCB.getOperand(k).getInst(),
1058               HexagonMCInstrInfo::hasExtenderForIndex(MCB, k - 1),
1059               *MCB.getOperand(j).getInst(),
1060               HexagonMCInstrInfo::hasExtenderForIndex(MCB, j - 1),
1061               bisReversable, STI)) {
1062         // Get iClass.
1063         unsigned iClass = iClassOfDuplexPair(
1064             getDuplexCandidateGroup(*MCB.getOperand(k).getInst()),
1065             getDuplexCandidateGroup(*MCB.getOperand(j).getInst()));
1066 
1067         // Save off pairs for duplex checking.
1068         duplexToTry.push_back(DuplexCandidate(j, k, iClass));
1069         LLVM_DEBUG(dbgs() << "adding pair: " << j << "," << k << ":"
1070                           << MCB.getOperand(j).getInst()->getOpcode() << ","
1071                           << MCB.getOperand(k).getInst()->getOpcode() << "\n");
1072         continue;
1073       } else {
1074         LLVM_DEBUG(dbgs() << "skipping pair: " << j << "," << k << ":"
1075                           << MCB.getOperand(j).getInst()->getOpcode() << ","
1076                           << MCB.getOperand(k).getInst()->getOpcode() << "\n");
1077       }
1078 
1079       // Try reverse.
1080       if (bisReversable) {
1081         if (isOrderedDuplexPair(
1082                 MCII, *MCB.getOperand(j).getInst(),
1083                 HexagonMCInstrInfo::hasExtenderForIndex(MCB, j - 1),
1084                 *MCB.getOperand(k).getInst(),
1085                 HexagonMCInstrInfo::hasExtenderForIndex(MCB, k - 1),
1086                 bisReversable, STI)) {
1087           // Get iClass.
1088           unsigned iClass = iClassOfDuplexPair(
1089               getDuplexCandidateGroup(*MCB.getOperand(j).getInst()),
1090               getDuplexCandidateGroup(*MCB.getOperand(k).getInst()));
1091 
1092           // Save off pairs for duplex checking.
1093           duplexToTry.push_back(DuplexCandidate(k, j, iClass));
1094           LLVM_DEBUG(dbgs()
1095                      << "adding pair:" << k << "," << j << ":"
1096                      << MCB.getOperand(j).getInst()->getOpcode() << ","
1097                      << MCB.getOperand(k).getInst()->getOpcode() << "\n");
1098         } else {
1099           LLVM_DEBUG(dbgs()
1100                      << "skipping pair: " << k << "," << j << ":"
1101                      << MCB.getOperand(j).getInst()->getOpcode() << ","
1102                      << MCB.getOperand(k).getInst()->getOpcode() << "\n");
1103         }
1104       }
1105     }
1106   }
1107   return duplexToTry;
1108 }
1109