AArch64: disable FastISel for large code model.
[oota-llvm.git] / lib / Target / AArch64 / AArch64FastISel.cpp
1 //===-- AArch6464FastISel.cpp - AArch64 FastISel implementation -----------===//
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 AArch64-specific support for the FastISel class. Some
11 // of the target-specific code is generated by tablegen in the file
12 // AArch64GenFastISel.inc, which is #included here.
13 //
14 //===----------------------------------------------------------------------===//
15
16 #include "AArch64.h"
17 #include "AArch64TargetMachine.h"
18 #include "AArch64Subtarget.h"
19 #include "AArch64CallingConv.h"
20 #include "MCTargetDesc/AArch64AddressingModes.h"
21 #include "llvm/CodeGen/CallingConvLower.h"
22 #include "llvm/CodeGen/FastISel.h"
23 #include "llvm/CodeGen/FunctionLoweringInfo.h"
24 #include "llvm/CodeGen/MachineConstantPool.h"
25 #include "llvm/CodeGen/MachineFrameInfo.h"
26 #include "llvm/CodeGen/MachineInstrBuilder.h"
27 #include "llvm/CodeGen/MachineRegisterInfo.h"
28 #include "llvm/IR/CallingConv.h"
29 #include "llvm/IR/DataLayout.h"
30 #include "llvm/IR/DerivedTypes.h"
31 #include "llvm/IR/Function.h"
32 #include "llvm/IR/GetElementPtrTypeIterator.h"
33 #include "llvm/IR/GlobalAlias.h"
34 #include "llvm/IR/GlobalVariable.h"
35 #include "llvm/IR/Instructions.h"
36 #include "llvm/IR/IntrinsicInst.h"
37 #include "llvm/IR/Operator.h"
38 #include "llvm/Support/CommandLine.h"
39 using namespace llvm;
40
41 namespace {
42
43 class AArch64FastISel : public FastISel {
44
45   class Address {
46   public:
47     typedef enum {
48       RegBase,
49       FrameIndexBase
50     } BaseKind;
51
52   private:
53     BaseKind Kind;
54     union {
55       unsigned Reg;
56       int FI;
57     } Base;
58     int64_t Offset;
59
60   public:
61     Address() : Kind(RegBase), Offset(0) { Base.Reg = 0; }
62     void setKind(BaseKind K) { Kind = K; }
63     BaseKind getKind() const { return Kind; }
64     bool isRegBase() const { return Kind == RegBase; }
65     bool isFIBase() const { return Kind == FrameIndexBase; }
66     void setReg(unsigned Reg) {
67       assert(isRegBase() && "Invalid base register access!");
68       Base.Reg = Reg;
69     }
70     unsigned getReg() const {
71       assert(isRegBase() && "Invalid base register access!");
72       return Base.Reg;
73     }
74     void setFI(unsigned FI) {
75       assert(isFIBase() && "Invalid base frame index  access!");
76       Base.FI = FI;
77     }
78     unsigned getFI() const {
79       assert(isFIBase() && "Invalid base frame index access!");
80       return Base.FI;
81     }
82     void setOffset(int64_t O) { Offset = O; }
83     int64_t getOffset() { return Offset; }
84
85     bool isValid() { return isFIBase() || (isRegBase() && getReg() != 0); }
86   };
87
88   /// Subtarget - Keep a pointer to the AArch64Subtarget around so that we can
89   /// make the right decision when generating code for different targets.
90   const AArch64Subtarget *Subtarget;
91   LLVMContext *Context;
92
93 private:
94   // Selection routines.
95   bool SelectLoad(const Instruction *I);
96   bool SelectStore(const Instruction *I);
97   bool SelectBranch(const Instruction *I);
98   bool SelectIndirectBr(const Instruction *I);
99   bool SelectCmp(const Instruction *I);
100   bool SelectSelect(const Instruction *I);
101   bool SelectFPExt(const Instruction *I);
102   bool SelectFPTrunc(const Instruction *I);
103   bool SelectFPToInt(const Instruction *I, bool Signed);
104   bool SelectIntToFP(const Instruction *I, bool Signed);
105   bool SelectRem(const Instruction *I, unsigned ISDOpcode);
106   bool SelectCall(const Instruction *I, const char *IntrMemName);
107   bool SelectIntrinsicCall(const IntrinsicInst &I);
108   bool SelectRet(const Instruction *I);
109   bool SelectTrunc(const Instruction *I);
110   bool SelectIntExt(const Instruction *I);
111   bool SelectMul(const Instruction *I);
112
113   // Utility helper routines.
114   bool isTypeLegal(Type *Ty, MVT &VT);
115   bool isLoadStoreTypeLegal(Type *Ty, MVT &VT);
116   bool ComputeAddress(const Value *Obj, Address &Addr);
117   bool SimplifyAddress(Address &Addr, MVT VT, int64_t ScaleFactor,
118                        bool UseUnscaled);
119   void AddLoadStoreOperands(Address &Addr, const MachineInstrBuilder &MIB,
120                             unsigned Flags, bool UseUnscaled);
121   bool IsMemCpySmall(uint64_t Len, unsigned Alignment);
122   bool TryEmitSmallMemCpy(Address Dest, Address Src, uint64_t Len,
123                           unsigned Alignment);
124   // Emit functions.
125   bool EmitCmp(Value *Src1Value, Value *Src2Value, bool isZExt);
126   bool EmitLoad(MVT VT, unsigned &ResultReg, Address Addr,
127                 bool UseUnscaled = false);
128   bool EmitStore(MVT VT, unsigned SrcReg, Address Addr,
129                  bool UseUnscaled = false);
130   unsigned EmitIntExt(MVT SrcVT, unsigned SrcReg, MVT DestVT, bool isZExt);
131   unsigned Emiti1Ext(unsigned SrcReg, MVT DestVT, bool isZExt);
132
133   unsigned AArch64MaterializeFP(const ConstantFP *CFP, MVT VT);
134   unsigned AArch64MaterializeGV(const GlobalValue *GV);
135
136   // Call handling routines.
137 private:
138   CCAssignFn *CCAssignFnForCall(CallingConv::ID CC) const;
139   bool ProcessCallArgs(SmallVectorImpl<Value *> &Args,
140                        SmallVectorImpl<unsigned> &ArgRegs,
141                        SmallVectorImpl<MVT> &ArgVTs,
142                        SmallVectorImpl<ISD::ArgFlagsTy> &ArgFlags,
143                        SmallVectorImpl<unsigned> &RegArgs, CallingConv::ID CC,
144                        unsigned &NumBytes);
145   bool FinishCall(MVT RetVT, SmallVectorImpl<unsigned> &UsedRegs,
146                   const Instruction *I, CallingConv::ID CC, unsigned &NumBytes);
147
148 public:
149   // Backend specific FastISel code.
150   unsigned TargetMaterializeAlloca(const AllocaInst *AI) override;
151   unsigned TargetMaterializeConstant(const Constant *C) override;
152
153   explicit AArch64FastISel(FunctionLoweringInfo &funcInfo,
154                          const TargetLibraryInfo *libInfo)
155       : FastISel(funcInfo, libInfo) {
156     Subtarget = &TM.getSubtarget<AArch64Subtarget>();
157     Context = &funcInfo.Fn->getContext();
158   }
159
160   bool TargetSelectInstruction(const Instruction *I) override;
161
162 #include "AArch64GenFastISel.inc"
163 };
164
165 } // end anonymous namespace
166
167 #include "AArch64GenCallingConv.inc"
168
169 CCAssignFn *AArch64FastISel::CCAssignFnForCall(CallingConv::ID CC) const {
170   if (CC == CallingConv::WebKit_JS)
171     return CC_AArch64_WebKit_JS;
172   return Subtarget->isTargetDarwin() ? CC_AArch64_DarwinPCS : CC_AArch64_AAPCS;
173 }
174
175 unsigned AArch64FastISel::TargetMaterializeAlloca(const AllocaInst *AI) {
176   assert(TLI.getValueType(AI->getType(), true) == MVT::i64 &&
177          "Alloca should always return a pointer.");
178
179   // Don't handle dynamic allocas.
180   if (!FuncInfo.StaticAllocaMap.count(AI))
181     return 0;
182
183   DenseMap<const AllocaInst *, int>::iterator SI =
184       FuncInfo.StaticAllocaMap.find(AI);
185
186   if (SI != FuncInfo.StaticAllocaMap.end()) {
187     unsigned ResultReg = createResultReg(&AArch64::GPR64RegClass);
188     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ADDXri),
189             ResultReg)
190         .addFrameIndex(SI->second)
191         .addImm(0)
192         .addImm(0);
193     return ResultReg;
194   }
195
196   return 0;
197 }
198
199 unsigned AArch64FastISel::AArch64MaterializeFP(const ConstantFP *CFP, MVT VT) {
200   if (VT != MVT::f32 && VT != MVT::f64)
201     return 0;
202
203   const APFloat Val = CFP->getValueAPF();
204   bool is64bit = (VT == MVT::f64);
205
206   // This checks to see if we can use FMOV instructions to materialize
207   // a constant, otherwise we have to materialize via the constant pool.
208   if (TLI.isFPImmLegal(Val, VT)) {
209     int Imm;
210     unsigned Opc;
211     if (is64bit) {
212       Imm = AArch64_AM::getFP64Imm(Val);
213       Opc = AArch64::FMOVDi;
214     } else {
215       Imm = AArch64_AM::getFP32Imm(Val);
216       Opc = AArch64::FMOVSi;
217     }
218     unsigned ResultReg = createResultReg(TLI.getRegClassFor(VT));
219     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(Opc), ResultReg)
220         .addImm(Imm);
221     return ResultReg;
222   }
223
224   // Materialize via constant pool.  MachineConstantPool wants an explicit
225   // alignment.
226   unsigned Align = DL.getPrefTypeAlignment(CFP->getType());
227   if (Align == 0)
228     Align = DL.getTypeAllocSize(CFP->getType());
229
230   unsigned Idx = MCP.getConstantPoolIndex(cast<Constant>(CFP), Align);
231   unsigned ADRPReg = createResultReg(&AArch64::GPR64commonRegClass);
232   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ADRP),
233           ADRPReg).addConstantPoolIndex(Idx, 0, AArch64II::MO_PAGE);
234
235   unsigned Opc = is64bit ? AArch64::LDRDui : AArch64::LDRSui;
236   unsigned ResultReg = createResultReg(TLI.getRegClassFor(VT));
237   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(Opc), ResultReg)
238       .addReg(ADRPReg)
239       .addConstantPoolIndex(Idx, 0, AArch64II::MO_PAGEOFF | AArch64II::MO_NC);
240   return ResultReg;
241 }
242
243 unsigned AArch64FastISel::AArch64MaterializeGV(const GlobalValue *GV) {
244   // We can't handle thread-local variables quickly yet. Unfortunately we have
245   // to peer through any aliases to find out if that rule applies.
246   const GlobalValue *TLSGV = GV;
247   if (const GlobalAlias *GA = dyn_cast<GlobalAlias>(GV))
248     TLSGV = GA->getAliasee();
249
250   // MachO still uses GOT for large code-model accesses, but ELF requires
251   // movz/movk sequences, which FastISel doesn't handle yet.
252   if (TM.getCodeModel() != CodeModel::Small && !Subtarget->isTargetMachO())
253     return 0;
254
255   if (const GlobalVariable *GVar = dyn_cast<GlobalVariable>(TLSGV))
256     if (GVar->isThreadLocal())
257       return 0;
258
259   unsigned char OpFlags = Subtarget->ClassifyGlobalReference(GV, TM);
260
261   EVT DestEVT = TLI.getValueType(GV->getType(), true);
262   if (!DestEVT.isSimple())
263     return 0;
264
265   unsigned ADRPReg = createResultReg(&AArch64::GPR64commonRegClass);
266   unsigned ResultReg;
267
268   if (OpFlags & AArch64II::MO_GOT) {
269     // ADRP + LDRX
270     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ADRP),
271             ADRPReg)
272         .addGlobalAddress(GV, 0, AArch64II::MO_GOT | AArch64II::MO_PAGE);
273
274     ResultReg = createResultReg(&AArch64::GPR64RegClass);
275     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::LDRXui),
276             ResultReg)
277         .addReg(ADRPReg)
278         .addGlobalAddress(GV, 0, AArch64II::MO_GOT | AArch64II::MO_PAGEOFF |
279                           AArch64II::MO_NC);
280   } else {
281     // ADRP + ADDX
282     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ADRP),
283             ADRPReg).addGlobalAddress(GV, 0, AArch64II::MO_PAGE);
284
285     ResultReg = createResultReg(&AArch64::GPR64spRegClass);
286     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ADDXri),
287             ResultReg)
288         .addReg(ADRPReg)
289         .addGlobalAddress(GV, 0, AArch64II::MO_PAGEOFF | AArch64II::MO_NC)
290         .addImm(0);
291   }
292   return ResultReg;
293 }
294
295 unsigned AArch64FastISel::TargetMaterializeConstant(const Constant *C) {
296   EVT CEVT = TLI.getValueType(C->getType(), true);
297
298   // Only handle simple types.
299   if (!CEVT.isSimple())
300     return 0;
301   MVT VT = CEVT.getSimpleVT();
302
303   // FIXME: Handle ConstantInt.
304   if (const ConstantFP *CFP = dyn_cast<ConstantFP>(C))
305     return AArch64MaterializeFP(CFP, VT);
306   else if (const GlobalValue *GV = dyn_cast<GlobalValue>(C))
307     return AArch64MaterializeGV(GV);
308
309   return 0;
310 }
311
312 // Computes the address to get to an object.
313 bool AArch64FastISel::ComputeAddress(const Value *Obj, Address &Addr) {
314   const User *U = nullptr;
315   unsigned Opcode = Instruction::UserOp1;
316   if (const Instruction *I = dyn_cast<Instruction>(Obj)) {
317     // Don't walk into other basic blocks unless the object is an alloca from
318     // another block, otherwise it may not have a virtual register assigned.
319     if (FuncInfo.StaticAllocaMap.count(static_cast<const AllocaInst *>(Obj)) ||
320         FuncInfo.MBBMap[I->getParent()] == FuncInfo.MBB) {
321       Opcode = I->getOpcode();
322       U = I;
323     }
324   } else if (const ConstantExpr *C = dyn_cast<ConstantExpr>(Obj)) {
325     Opcode = C->getOpcode();
326     U = C;
327   }
328
329   if (const PointerType *Ty = dyn_cast<PointerType>(Obj->getType()))
330     if (Ty->getAddressSpace() > 255)
331       // Fast instruction selection doesn't support the special
332       // address spaces.
333       return false;
334
335   switch (Opcode) {
336   default:
337     break;
338   case Instruction::BitCast: {
339     // Look through bitcasts.
340     return ComputeAddress(U->getOperand(0), Addr);
341   }
342   case Instruction::IntToPtr: {
343     // Look past no-op inttoptrs.
344     if (TLI.getValueType(U->getOperand(0)->getType()) == TLI.getPointerTy())
345       return ComputeAddress(U->getOperand(0), Addr);
346     break;
347   }
348   case Instruction::PtrToInt: {
349     // Look past no-op ptrtoints.
350     if (TLI.getValueType(U->getType()) == TLI.getPointerTy())
351       return ComputeAddress(U->getOperand(0), Addr);
352     break;
353   }
354   case Instruction::GetElementPtr: {
355     Address SavedAddr = Addr;
356     uint64_t TmpOffset = Addr.getOffset();
357
358     // Iterate through the GEP folding the constants into offsets where
359     // we can.
360     gep_type_iterator GTI = gep_type_begin(U);
361     for (User::const_op_iterator i = U->op_begin() + 1, e = U->op_end(); i != e;
362          ++i, ++GTI) {
363       const Value *Op = *i;
364       if (StructType *STy = dyn_cast<StructType>(*GTI)) {
365         const StructLayout *SL = DL.getStructLayout(STy);
366         unsigned Idx = cast<ConstantInt>(Op)->getZExtValue();
367         TmpOffset += SL->getElementOffset(Idx);
368       } else {
369         uint64_t S = DL.getTypeAllocSize(GTI.getIndexedType());
370         for (;;) {
371           if (const ConstantInt *CI = dyn_cast<ConstantInt>(Op)) {
372             // Constant-offset addressing.
373             TmpOffset += CI->getSExtValue() * S;
374             break;
375           }
376           if (canFoldAddIntoGEP(U, Op)) {
377             // A compatible add with a constant operand. Fold the constant.
378             ConstantInt *CI =
379                 cast<ConstantInt>(cast<AddOperator>(Op)->getOperand(1));
380             TmpOffset += CI->getSExtValue() * S;
381             // Iterate on the other operand.
382             Op = cast<AddOperator>(Op)->getOperand(0);
383             continue;
384           }
385           // Unsupported
386           goto unsupported_gep;
387         }
388       }
389     }
390
391     // Try to grab the base operand now.
392     Addr.setOffset(TmpOffset);
393     if (ComputeAddress(U->getOperand(0), Addr))
394       return true;
395
396     // We failed, restore everything and try the other options.
397     Addr = SavedAddr;
398
399   unsupported_gep:
400     break;
401   }
402   case Instruction::Alloca: {
403     const AllocaInst *AI = cast<AllocaInst>(Obj);
404     DenseMap<const AllocaInst *, int>::iterator SI =
405         FuncInfo.StaticAllocaMap.find(AI);
406     if (SI != FuncInfo.StaticAllocaMap.end()) {
407       Addr.setKind(Address::FrameIndexBase);
408       Addr.setFI(SI->second);
409       return true;
410     }
411     break;
412   }
413   }
414
415   // Try to get this in a register if nothing else has worked.
416   if (!Addr.isValid())
417     Addr.setReg(getRegForValue(Obj));
418   return Addr.isValid();
419 }
420
421 bool AArch64FastISel::isTypeLegal(Type *Ty, MVT &VT) {
422   EVT evt = TLI.getValueType(Ty, true);
423
424   // Only handle simple types.
425   if (evt == MVT::Other || !evt.isSimple())
426     return false;
427   VT = evt.getSimpleVT();
428
429   // This is a legal type, but it's not something we handle in fast-isel.
430   if (VT == MVT::f128)
431     return false;
432
433   // Handle all other legal types, i.e. a register that will directly hold this
434   // value.
435   return TLI.isTypeLegal(VT);
436 }
437
438 bool AArch64FastISel::isLoadStoreTypeLegal(Type *Ty, MVT &VT) {
439   if (isTypeLegal(Ty, VT))
440     return true;
441
442   // If this is a type than can be sign or zero-extended to a basic operation
443   // go ahead and accept it now. For stores, this reflects truncation.
444   if (VT == MVT::i1 || VT == MVT::i8 || VT == MVT::i16)
445     return true;
446
447   return false;
448 }
449
450 bool AArch64FastISel::SimplifyAddress(Address &Addr, MVT VT,
451                                       int64_t ScaleFactor, bool UseUnscaled) {
452   bool needsLowering = false;
453   int64_t Offset = Addr.getOffset();
454   switch (VT.SimpleTy) {
455   default:
456     return false;
457   case MVT::i1:
458   case MVT::i8:
459   case MVT::i16:
460   case MVT::i32:
461   case MVT::i64:
462   case MVT::f32:
463   case MVT::f64:
464     if (!UseUnscaled)
465       // Using scaled, 12-bit, unsigned immediate offsets.
466       needsLowering = ((Offset & 0xfff) != Offset);
467     else
468       // Using unscaled, 9-bit, signed immediate offsets.
469       needsLowering = (Offset > 256 || Offset < -256);
470     break;
471   }
472
473   // FIXME: If this is a stack pointer and the offset needs to be simplified
474   // then put the alloca address into a register, set the base type back to
475   // register and continue. This should almost never happen.
476   if (needsLowering && Addr.getKind() == Address::FrameIndexBase) {
477     return false;
478   }
479
480   // Since the offset is too large for the load/store instruction get the
481   // reg+offset into a register.
482   if (needsLowering) {
483     uint64_t UnscaledOffset = Addr.getOffset() * ScaleFactor;
484     unsigned ResultReg = FastEmit_ri_(MVT::i64, ISD::ADD, Addr.getReg(), false,
485                                       UnscaledOffset, MVT::i64);
486     if (ResultReg == 0)
487       return false;
488     Addr.setReg(ResultReg);
489     Addr.setOffset(0);
490   }
491   return true;
492 }
493
494 void AArch64FastISel::AddLoadStoreOperands(Address &Addr,
495                                            const MachineInstrBuilder &MIB,
496                                            unsigned Flags, bool UseUnscaled) {
497   int64_t Offset = Addr.getOffset();
498   // Frame base works a bit differently. Handle it separately.
499   if (Addr.getKind() == Address::FrameIndexBase) {
500     int FI = Addr.getFI();
501     // FIXME: We shouldn't be using getObjectSize/getObjectAlignment.  The size
502     // and alignment should be based on the VT.
503     MachineMemOperand *MMO = FuncInfo.MF->getMachineMemOperand(
504         MachinePointerInfo::getFixedStack(FI, Offset), Flags,
505         MFI.getObjectSize(FI), MFI.getObjectAlignment(FI));
506     // Now add the rest of the operands.
507     MIB.addFrameIndex(FI).addImm(Offset).addMemOperand(MMO);
508   } else {
509     // Now add the rest of the operands.
510     MIB.addReg(Addr.getReg());
511     MIB.addImm(Offset);
512   }
513 }
514
515 bool AArch64FastISel::EmitLoad(MVT VT, unsigned &ResultReg, Address Addr,
516                                bool UseUnscaled) {
517   // Negative offsets require unscaled, 9-bit, signed immediate offsets.
518   // Otherwise, we try using scaled, 12-bit, unsigned immediate offsets.
519   if (!UseUnscaled && Addr.getOffset() < 0)
520     UseUnscaled = true;
521
522   unsigned Opc;
523   const TargetRegisterClass *RC;
524   bool VTIsi1 = false;
525   int64_t ScaleFactor = 0;
526   switch (VT.SimpleTy) {
527   default:
528     return false;
529   case MVT::i1:
530     VTIsi1 = true;
531   // Intentional fall-through.
532   case MVT::i8:
533     Opc = UseUnscaled ? AArch64::LDURBBi : AArch64::LDRBBui;
534     RC = &AArch64::GPR32RegClass;
535     ScaleFactor = 1;
536     break;
537   case MVT::i16:
538     Opc = UseUnscaled ? AArch64::LDURHHi : AArch64::LDRHHui;
539     RC = &AArch64::GPR32RegClass;
540     ScaleFactor = 2;
541     break;
542   case MVT::i32:
543     Opc = UseUnscaled ? AArch64::LDURWi : AArch64::LDRWui;
544     RC = &AArch64::GPR32RegClass;
545     ScaleFactor = 4;
546     break;
547   case MVT::i64:
548     Opc = UseUnscaled ? AArch64::LDURXi : AArch64::LDRXui;
549     RC = &AArch64::GPR64RegClass;
550     ScaleFactor = 8;
551     break;
552   case MVT::f32:
553     Opc = UseUnscaled ? AArch64::LDURSi : AArch64::LDRSui;
554     RC = TLI.getRegClassFor(VT);
555     ScaleFactor = 4;
556     break;
557   case MVT::f64:
558     Opc = UseUnscaled ? AArch64::LDURDi : AArch64::LDRDui;
559     RC = TLI.getRegClassFor(VT);
560     ScaleFactor = 8;
561     break;
562   }
563   // Scale the offset.
564   if (!UseUnscaled) {
565     int64_t Offset = Addr.getOffset();
566     if (Offset & (ScaleFactor - 1))
567       // Retry using an unscaled, 9-bit, signed immediate offset.
568       return EmitLoad(VT, ResultReg, Addr, /*UseUnscaled*/ true);
569
570     Addr.setOffset(Offset / ScaleFactor);
571   }
572
573   // Simplify this down to something we can handle.
574   if (!SimplifyAddress(Addr, VT, UseUnscaled ? 1 : ScaleFactor, UseUnscaled))
575     return false;
576
577   // Create the base instruction, then add the operands.
578   ResultReg = createResultReg(RC);
579   MachineInstrBuilder MIB = BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
580                                     TII.get(Opc), ResultReg);
581   AddLoadStoreOperands(Addr, MIB, MachineMemOperand::MOLoad, UseUnscaled);
582
583   // Loading an i1 requires special handling.
584   if (VTIsi1) {
585     MRI.constrainRegClass(ResultReg, &AArch64::GPR32RegClass);
586     unsigned ANDReg = createResultReg(&AArch64::GPR32spRegClass);
587     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ANDWri),
588             ANDReg)
589         .addReg(ResultReg)
590         .addImm(AArch64_AM::encodeLogicalImmediate(1, 32));
591     ResultReg = ANDReg;
592   }
593   return true;
594 }
595
596 bool AArch64FastISel::SelectLoad(const Instruction *I) {
597   MVT VT;
598   // Verify we have a legal type before going any further.  Currently, we handle
599   // simple types that will directly fit in a register (i32/f32/i64/f64) or
600   // those that can be sign or zero-extended to a basic operation (i1/i8/i16).
601   if (!isLoadStoreTypeLegal(I->getType(), VT) || cast<LoadInst>(I)->isAtomic())
602     return false;
603
604   // See if we can handle this address.
605   Address Addr;
606   if (!ComputeAddress(I->getOperand(0), Addr))
607     return false;
608
609   unsigned ResultReg;
610   if (!EmitLoad(VT, ResultReg, Addr))
611     return false;
612
613   UpdateValueMap(I, ResultReg);
614   return true;
615 }
616
617 bool AArch64FastISel::EmitStore(MVT VT, unsigned SrcReg, Address Addr,
618                                 bool UseUnscaled) {
619   // Negative offsets require unscaled, 9-bit, signed immediate offsets.
620   // Otherwise, we try using scaled, 12-bit, unsigned immediate offsets.
621   if (!UseUnscaled && Addr.getOffset() < 0)
622     UseUnscaled = true;
623
624   unsigned StrOpc;
625   bool VTIsi1 = false;
626   int64_t ScaleFactor = 0;
627   // Using scaled, 12-bit, unsigned immediate offsets.
628   switch (VT.SimpleTy) {
629   default:
630     return false;
631   case MVT::i1:
632     VTIsi1 = true;
633   case MVT::i8:
634     StrOpc = UseUnscaled ? AArch64::STURBBi : AArch64::STRBBui;
635     ScaleFactor = 1;
636     break;
637   case MVT::i16:
638     StrOpc = UseUnscaled ? AArch64::STURHHi : AArch64::STRHHui;
639     ScaleFactor = 2;
640     break;
641   case MVT::i32:
642     StrOpc = UseUnscaled ? AArch64::STURWi : AArch64::STRWui;
643     ScaleFactor = 4;
644     break;
645   case MVT::i64:
646     StrOpc = UseUnscaled ? AArch64::STURXi : AArch64::STRXui;
647     ScaleFactor = 8;
648     break;
649   case MVT::f32:
650     StrOpc = UseUnscaled ? AArch64::STURSi : AArch64::STRSui;
651     ScaleFactor = 4;
652     break;
653   case MVT::f64:
654     StrOpc = UseUnscaled ? AArch64::STURDi : AArch64::STRDui;
655     ScaleFactor = 8;
656     break;
657   }
658   // Scale the offset.
659   if (!UseUnscaled) {
660     int64_t Offset = Addr.getOffset();
661     if (Offset & (ScaleFactor - 1))
662       // Retry using an unscaled, 9-bit, signed immediate offset.
663       return EmitStore(VT, SrcReg, Addr, /*UseUnscaled*/ true);
664
665     Addr.setOffset(Offset / ScaleFactor);
666   }
667
668   // Simplify this down to something we can handle.
669   if (!SimplifyAddress(Addr, VT, UseUnscaled ? 1 : ScaleFactor, UseUnscaled))
670     return false;
671
672   // Storing an i1 requires special handling.
673   if (VTIsi1) {
674     MRI.constrainRegClass(SrcReg, &AArch64::GPR32RegClass);
675     unsigned ANDReg = createResultReg(&AArch64::GPR32spRegClass);
676     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ANDWri),
677             ANDReg)
678         .addReg(SrcReg)
679         .addImm(AArch64_AM::encodeLogicalImmediate(1, 32));
680     SrcReg = ANDReg;
681   }
682   // Create the base instruction, then add the operands.
683   MachineInstrBuilder MIB = BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
684                                     TII.get(StrOpc)).addReg(SrcReg);
685   AddLoadStoreOperands(Addr, MIB, MachineMemOperand::MOStore, UseUnscaled);
686   return true;
687 }
688
689 bool AArch64FastISel::SelectStore(const Instruction *I) {
690   MVT VT;
691   Value *Op0 = I->getOperand(0);
692   // Verify we have a legal type before going any further.  Currently, we handle
693   // simple types that will directly fit in a register (i32/f32/i64/f64) or
694   // those that can be sign or zero-extended to a basic operation (i1/i8/i16).
695   if (!isLoadStoreTypeLegal(Op0->getType(), VT) ||
696       cast<StoreInst>(I)->isAtomic())
697     return false;
698
699   // Get the value to be stored into a register.
700   unsigned SrcReg = getRegForValue(Op0);
701   if (SrcReg == 0)
702     return false;
703
704   // See if we can handle this address.
705   Address Addr;
706   if (!ComputeAddress(I->getOperand(1), Addr))
707     return false;
708
709   if (!EmitStore(VT, SrcReg, Addr))
710     return false;
711   return true;
712 }
713
714 static AArch64CC::CondCode getCompareCC(CmpInst::Predicate Pred) {
715   switch (Pred) {
716   case CmpInst::FCMP_ONE:
717   case CmpInst::FCMP_UEQ:
718   default:
719     // AL is our "false" for now. The other two need more compares.
720     return AArch64CC::AL;
721   case CmpInst::ICMP_EQ:
722   case CmpInst::FCMP_OEQ:
723     return AArch64CC::EQ;
724   case CmpInst::ICMP_SGT:
725   case CmpInst::FCMP_OGT:
726     return AArch64CC::GT;
727   case CmpInst::ICMP_SGE:
728   case CmpInst::FCMP_OGE:
729     return AArch64CC::GE;
730   case CmpInst::ICMP_UGT:
731   case CmpInst::FCMP_UGT:
732     return AArch64CC::HI;
733   case CmpInst::FCMP_OLT:
734     return AArch64CC::MI;
735   case CmpInst::ICMP_ULE:
736   case CmpInst::FCMP_OLE:
737     return AArch64CC::LS;
738   case CmpInst::FCMP_ORD:
739     return AArch64CC::VC;
740   case CmpInst::FCMP_UNO:
741     return AArch64CC::VS;
742   case CmpInst::FCMP_UGE:
743     return AArch64CC::PL;
744   case CmpInst::ICMP_SLT:
745   case CmpInst::FCMP_ULT:
746     return AArch64CC::LT;
747   case CmpInst::ICMP_SLE:
748   case CmpInst::FCMP_ULE:
749     return AArch64CC::LE;
750   case CmpInst::FCMP_UNE:
751   case CmpInst::ICMP_NE:
752     return AArch64CC::NE;
753   case CmpInst::ICMP_UGE:
754     return AArch64CC::HS;
755   case CmpInst::ICMP_ULT:
756     return AArch64CC::LO;
757   }
758 }
759
760 bool AArch64FastISel::SelectBranch(const Instruction *I) {
761   const BranchInst *BI = cast<BranchInst>(I);
762   MachineBasicBlock *TBB = FuncInfo.MBBMap[BI->getSuccessor(0)];
763   MachineBasicBlock *FBB = FuncInfo.MBBMap[BI->getSuccessor(1)];
764
765   if (const CmpInst *CI = dyn_cast<CmpInst>(BI->getCondition())) {
766     if (CI->hasOneUse() && (CI->getParent() == I->getParent())) {
767       // We may not handle every CC for now.
768       AArch64CC::CondCode CC = getCompareCC(CI->getPredicate());
769       if (CC == AArch64CC::AL)
770         return false;
771
772       // Emit the cmp.
773       if (!EmitCmp(CI->getOperand(0), CI->getOperand(1), CI->isUnsigned()))
774         return false;
775
776       // Emit the branch.
777       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::Bcc))
778           .addImm(CC)
779           .addMBB(TBB);
780       FuncInfo.MBB->addSuccessor(TBB);
781
782       FastEmitBranch(FBB, DbgLoc);
783       return true;
784     }
785   } else if (TruncInst *TI = dyn_cast<TruncInst>(BI->getCondition())) {
786     MVT SrcVT;
787     if (TI->hasOneUse() && TI->getParent() == I->getParent() &&
788         (isLoadStoreTypeLegal(TI->getOperand(0)->getType(), SrcVT))) {
789       unsigned CondReg = getRegForValue(TI->getOperand(0));
790       if (CondReg == 0)
791         return false;
792
793       // Issue an extract_subreg to get the lower 32-bits.
794       if (SrcVT == MVT::i64)
795         CondReg = FastEmitInst_extractsubreg(MVT::i32, CondReg, /*Kill=*/true,
796                                              AArch64::sub_32);
797
798       MRI.constrainRegClass(CondReg, &AArch64::GPR32RegClass);
799       unsigned ANDReg = createResultReg(&AArch64::GPR32spRegClass);
800       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
801               TII.get(AArch64::ANDWri), ANDReg)
802           .addReg(CondReg)
803           .addImm(AArch64_AM::encodeLogicalImmediate(1, 32));
804       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
805               TII.get(AArch64::SUBSWri))
806           .addReg(ANDReg)
807           .addReg(ANDReg)
808           .addImm(0)
809           .addImm(0);
810
811       unsigned CC = AArch64CC::NE;
812       if (FuncInfo.MBB->isLayoutSuccessor(TBB)) {
813         std::swap(TBB, FBB);
814         CC = AArch64CC::EQ;
815       }
816       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::Bcc))
817           .addImm(CC)
818           .addMBB(TBB);
819       FuncInfo.MBB->addSuccessor(TBB);
820       FastEmitBranch(FBB, DbgLoc);
821       return true;
822     }
823   } else if (const ConstantInt *CI =
824                  dyn_cast<ConstantInt>(BI->getCondition())) {
825     uint64_t Imm = CI->getZExtValue();
826     MachineBasicBlock *Target = (Imm == 0) ? FBB : TBB;
827     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::B))
828         .addMBB(Target);
829     FuncInfo.MBB->addSuccessor(Target);
830     return true;
831   }
832
833   unsigned CondReg = getRegForValue(BI->getCondition());
834   if (CondReg == 0)
835     return false;
836
837   // We've been divorced from our compare!  Our block was split, and
838   // now our compare lives in a predecessor block.  We musn't
839   // re-compare here, as the children of the compare aren't guaranteed
840   // live across the block boundary (we *could* check for this).
841   // Regardless, the compare has been done in the predecessor block,
842   // and it left a value for us in a virtual register.  Ergo, we test
843   // the one-bit value left in the virtual register.
844   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::SUBSWri),
845           AArch64::WZR)
846       .addReg(CondReg)
847       .addImm(0)
848       .addImm(0);
849
850   unsigned CC = AArch64CC::NE;
851   if (FuncInfo.MBB->isLayoutSuccessor(TBB)) {
852     std::swap(TBB, FBB);
853     CC = AArch64CC::EQ;
854   }
855
856   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::Bcc))
857       .addImm(CC)
858       .addMBB(TBB);
859   FuncInfo.MBB->addSuccessor(TBB);
860   FastEmitBranch(FBB, DbgLoc);
861   return true;
862 }
863
864 bool AArch64FastISel::SelectIndirectBr(const Instruction *I) {
865   const IndirectBrInst *BI = cast<IndirectBrInst>(I);
866   unsigned AddrReg = getRegForValue(BI->getOperand(0));
867   if (AddrReg == 0)
868     return false;
869
870   // Emit the indirect branch.
871   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::BR))
872       .addReg(AddrReg);
873
874   // Make sure the CFG is up-to-date.
875   for (unsigned i = 0, e = BI->getNumSuccessors(); i != e; ++i)
876     FuncInfo.MBB->addSuccessor(FuncInfo.MBBMap[BI->getSuccessor(i)]);
877
878   return true;
879 }
880
881 bool AArch64FastISel::EmitCmp(Value *Src1Value, Value *Src2Value, bool isZExt) {
882   Type *Ty = Src1Value->getType();
883   EVT SrcEVT = TLI.getValueType(Ty, true);
884   if (!SrcEVT.isSimple())
885     return false;
886   MVT SrcVT = SrcEVT.getSimpleVT();
887
888   // Check to see if the 2nd operand is a constant that we can encode directly
889   // in the compare.
890   uint64_t Imm;
891   bool UseImm = false;
892   bool isNegativeImm = false;
893   if (const ConstantInt *ConstInt = dyn_cast<ConstantInt>(Src2Value)) {
894     if (SrcVT == MVT::i64 || SrcVT == MVT::i32 || SrcVT == MVT::i16 ||
895         SrcVT == MVT::i8 || SrcVT == MVT::i1) {
896       const APInt &CIVal = ConstInt->getValue();
897
898       Imm = (isZExt) ? CIVal.getZExtValue() : CIVal.getSExtValue();
899       if (CIVal.isNegative()) {
900         isNegativeImm = true;
901         Imm = -Imm;
902       }
903       // FIXME: We can handle more immediates using shifts.
904       UseImm = ((Imm & 0xfff) == Imm);
905     }
906   } else if (const ConstantFP *ConstFP = dyn_cast<ConstantFP>(Src2Value)) {
907     if (SrcVT == MVT::f32 || SrcVT == MVT::f64)
908       if (ConstFP->isZero() && !ConstFP->isNegative())
909         UseImm = true;
910   }
911
912   unsigned ZReg;
913   unsigned CmpOpc;
914   bool isICmp = true;
915   bool needsExt = false;
916   switch (SrcVT.SimpleTy) {
917   default:
918     return false;
919   case MVT::i1:
920   case MVT::i8:
921   case MVT::i16:
922     needsExt = true;
923   // Intentional fall-through.
924   case MVT::i32:
925     ZReg = AArch64::WZR;
926     if (UseImm)
927       CmpOpc = isNegativeImm ? AArch64::ADDSWri : AArch64::SUBSWri;
928     else
929       CmpOpc = AArch64::SUBSWrr;
930     break;
931   case MVT::i64:
932     ZReg = AArch64::XZR;
933     if (UseImm)
934       CmpOpc = isNegativeImm ? AArch64::ADDSXri : AArch64::SUBSXri;
935     else
936       CmpOpc = AArch64::SUBSXrr;
937     break;
938   case MVT::f32:
939     isICmp = false;
940     CmpOpc = UseImm ? AArch64::FCMPSri : AArch64::FCMPSrr;
941     break;
942   case MVT::f64:
943     isICmp = false;
944     CmpOpc = UseImm ? AArch64::FCMPDri : AArch64::FCMPDrr;
945     break;
946   }
947
948   unsigned SrcReg1 = getRegForValue(Src1Value);
949   if (SrcReg1 == 0)
950     return false;
951
952   unsigned SrcReg2;
953   if (!UseImm) {
954     SrcReg2 = getRegForValue(Src2Value);
955     if (SrcReg2 == 0)
956       return false;
957   }
958
959   // We have i1, i8, or i16, we need to either zero extend or sign extend.
960   if (needsExt) {
961     SrcReg1 = EmitIntExt(SrcVT, SrcReg1, MVT::i32, isZExt);
962     if (SrcReg1 == 0)
963       return false;
964     if (!UseImm) {
965       SrcReg2 = EmitIntExt(SrcVT, SrcReg2, MVT::i32, isZExt);
966       if (SrcReg2 == 0)
967         return false;
968     }
969   }
970
971   if (isICmp) {
972     if (UseImm)
973       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(CmpOpc))
974           .addReg(ZReg)
975           .addReg(SrcReg1)
976           .addImm(Imm)
977           .addImm(0);
978     else
979       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(CmpOpc))
980           .addReg(ZReg)
981           .addReg(SrcReg1)
982           .addReg(SrcReg2);
983   } else {
984     if (UseImm)
985       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(CmpOpc))
986           .addReg(SrcReg1);
987     else
988       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(CmpOpc))
989           .addReg(SrcReg1)
990           .addReg(SrcReg2);
991   }
992   return true;
993 }
994
995 bool AArch64FastISel::SelectCmp(const Instruction *I) {
996   const CmpInst *CI = cast<CmpInst>(I);
997
998   // We may not handle every CC for now.
999   AArch64CC::CondCode CC = getCompareCC(CI->getPredicate());
1000   if (CC == AArch64CC::AL)
1001     return false;
1002
1003   // Emit the cmp.
1004   if (!EmitCmp(CI->getOperand(0), CI->getOperand(1), CI->isUnsigned()))
1005     return false;
1006
1007   // Now set a register based on the comparison.
1008   AArch64CC::CondCode invertedCC = getInvertedCondCode(CC);
1009   unsigned ResultReg = createResultReg(&AArch64::GPR32RegClass);
1010   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::CSINCWr),
1011           ResultReg)
1012       .addReg(AArch64::WZR)
1013       .addReg(AArch64::WZR)
1014       .addImm(invertedCC);
1015
1016   UpdateValueMap(I, ResultReg);
1017   return true;
1018 }
1019
1020 bool AArch64FastISel::SelectSelect(const Instruction *I) {
1021   const SelectInst *SI = cast<SelectInst>(I);
1022
1023   EVT DestEVT = TLI.getValueType(SI->getType(), true);
1024   if (!DestEVT.isSimple())
1025     return false;
1026
1027   MVT DestVT = DestEVT.getSimpleVT();
1028   if (DestVT != MVT::i32 && DestVT != MVT::i64 && DestVT != MVT::f32 &&
1029       DestVT != MVT::f64)
1030     return false;
1031
1032   unsigned CondReg = getRegForValue(SI->getCondition());
1033   if (CondReg == 0)
1034     return false;
1035   unsigned TrueReg = getRegForValue(SI->getTrueValue());
1036   if (TrueReg == 0)
1037     return false;
1038   unsigned FalseReg = getRegForValue(SI->getFalseValue());
1039   if (FalseReg == 0)
1040     return false;
1041
1042
1043   MRI.constrainRegClass(CondReg, &AArch64::GPR32RegClass);
1044   unsigned ANDReg = createResultReg(&AArch64::GPR32spRegClass);
1045   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ANDWri),
1046           ANDReg)
1047       .addReg(CondReg)
1048       .addImm(AArch64_AM::encodeLogicalImmediate(1, 32));
1049
1050   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::SUBSWri))
1051       .addReg(ANDReg)
1052       .addReg(ANDReg)
1053       .addImm(0)
1054       .addImm(0);
1055
1056   unsigned SelectOpc;
1057   switch (DestVT.SimpleTy) {
1058   default:
1059     return false;
1060   case MVT::i32:
1061     SelectOpc = AArch64::CSELWr;
1062     break;
1063   case MVT::i64:
1064     SelectOpc = AArch64::CSELXr;
1065     break;
1066   case MVT::f32:
1067     SelectOpc = AArch64::FCSELSrrr;
1068     break;
1069   case MVT::f64:
1070     SelectOpc = AArch64::FCSELDrrr;
1071     break;
1072   }
1073
1074   unsigned ResultReg = createResultReg(TLI.getRegClassFor(DestVT));
1075   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(SelectOpc),
1076           ResultReg)
1077       .addReg(TrueReg)
1078       .addReg(FalseReg)
1079       .addImm(AArch64CC::NE);
1080
1081   UpdateValueMap(I, ResultReg);
1082   return true;
1083 }
1084
1085 bool AArch64FastISel::SelectFPExt(const Instruction *I) {
1086   Value *V = I->getOperand(0);
1087   if (!I->getType()->isDoubleTy() || !V->getType()->isFloatTy())
1088     return false;
1089
1090   unsigned Op = getRegForValue(V);
1091   if (Op == 0)
1092     return false;
1093
1094   unsigned ResultReg = createResultReg(&AArch64::FPR64RegClass);
1095   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::FCVTDSr),
1096           ResultReg).addReg(Op);
1097   UpdateValueMap(I, ResultReg);
1098   return true;
1099 }
1100
1101 bool AArch64FastISel::SelectFPTrunc(const Instruction *I) {
1102   Value *V = I->getOperand(0);
1103   if (!I->getType()->isFloatTy() || !V->getType()->isDoubleTy())
1104     return false;
1105
1106   unsigned Op = getRegForValue(V);
1107   if (Op == 0)
1108     return false;
1109
1110   unsigned ResultReg = createResultReg(&AArch64::FPR32RegClass);
1111   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::FCVTSDr),
1112           ResultReg).addReg(Op);
1113   UpdateValueMap(I, ResultReg);
1114   return true;
1115 }
1116
1117 // FPToUI and FPToSI
1118 bool AArch64FastISel::SelectFPToInt(const Instruction *I, bool Signed) {
1119   MVT DestVT;
1120   if (!isTypeLegal(I->getType(), DestVT) || DestVT.isVector())
1121     return false;
1122
1123   unsigned SrcReg = getRegForValue(I->getOperand(0));
1124   if (SrcReg == 0)
1125     return false;
1126
1127   EVT SrcVT = TLI.getValueType(I->getOperand(0)->getType(), true);
1128   if (SrcVT == MVT::f128)
1129     return false;
1130
1131   unsigned Opc;
1132   if (SrcVT == MVT::f64) {
1133     if (Signed)
1134       Opc = (DestVT == MVT::i32) ? AArch64::FCVTZSUWDr : AArch64::FCVTZSUXDr;
1135     else
1136       Opc = (DestVT == MVT::i32) ? AArch64::FCVTZUUWDr : AArch64::FCVTZUUXDr;
1137   } else {
1138     if (Signed)
1139       Opc = (DestVT == MVT::i32) ? AArch64::FCVTZSUWSr : AArch64::FCVTZSUXSr;
1140     else
1141       Opc = (DestVT == MVT::i32) ? AArch64::FCVTZUUWSr : AArch64::FCVTZUUXSr;
1142   }
1143   unsigned ResultReg = createResultReg(
1144       DestVT == MVT::i32 ? &AArch64::GPR32RegClass : &AArch64::GPR64RegClass);
1145   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(Opc), ResultReg)
1146       .addReg(SrcReg);
1147   UpdateValueMap(I, ResultReg);
1148   return true;
1149 }
1150
1151 bool AArch64FastISel::SelectIntToFP(const Instruction *I, bool Signed) {
1152   MVT DestVT;
1153   if (!isTypeLegal(I->getType(), DestVT) || DestVT.isVector())
1154     return false;
1155   assert ((DestVT == MVT::f32 || DestVT == MVT::f64) &&
1156           "Unexpected value type.");
1157
1158   unsigned SrcReg = getRegForValue(I->getOperand(0));
1159   if (SrcReg == 0)
1160     return false;
1161
1162   EVT SrcVT = TLI.getValueType(I->getOperand(0)->getType(), true);
1163
1164   // Handle sign-extension.
1165   if (SrcVT == MVT::i16 || SrcVT == MVT::i8 || SrcVT == MVT::i1) {
1166     SrcReg =
1167         EmitIntExt(SrcVT.getSimpleVT(), SrcReg, MVT::i32, /*isZExt*/ !Signed);
1168     if (SrcReg == 0)
1169       return false;
1170   }
1171
1172   MRI.constrainRegClass(SrcReg, SrcVT == MVT::i64 ? &AArch64::GPR64RegClass
1173                                                   : &AArch64::GPR32RegClass);
1174
1175   unsigned Opc;
1176   if (SrcVT == MVT::i64) {
1177     if (Signed)
1178       Opc = (DestVT == MVT::f32) ? AArch64::SCVTFUXSri : AArch64::SCVTFUXDri;
1179     else
1180       Opc = (DestVT == MVT::f32) ? AArch64::UCVTFUXSri : AArch64::UCVTFUXDri;
1181   } else {
1182     if (Signed)
1183       Opc = (DestVT == MVT::f32) ? AArch64::SCVTFUWSri : AArch64::SCVTFUWDri;
1184     else
1185       Opc = (DestVT == MVT::f32) ? AArch64::UCVTFUWSri : AArch64::UCVTFUWDri;
1186   }
1187
1188   unsigned ResultReg = createResultReg(TLI.getRegClassFor(DestVT));
1189   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(Opc), ResultReg)
1190       .addReg(SrcReg);
1191   UpdateValueMap(I, ResultReg);
1192   return true;
1193 }
1194
1195 bool AArch64FastISel::ProcessCallArgs(
1196     SmallVectorImpl<Value *> &Args, SmallVectorImpl<unsigned> &ArgRegs,
1197     SmallVectorImpl<MVT> &ArgVTs, SmallVectorImpl<ISD::ArgFlagsTy> &ArgFlags,
1198     SmallVectorImpl<unsigned> &RegArgs, CallingConv::ID CC,
1199     unsigned &NumBytes) {
1200   SmallVector<CCValAssign, 16> ArgLocs;
1201   CCState CCInfo(CC, false, *FuncInfo.MF, TM, ArgLocs, *Context);
1202   CCInfo.AnalyzeCallOperands(ArgVTs, ArgFlags, CCAssignFnForCall(CC));
1203
1204   // Get a count of how many bytes are to be pushed on the stack.
1205   NumBytes = CCInfo.getNextStackOffset();
1206
1207   // Issue CALLSEQ_START
1208   unsigned AdjStackDown = TII.getCallFrameSetupOpcode();
1209   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AdjStackDown))
1210       .addImm(NumBytes);
1211
1212   // Process the args.
1213   for (unsigned i = 0, e = ArgLocs.size(); i != e; ++i) {
1214     CCValAssign &VA = ArgLocs[i];
1215     unsigned Arg = ArgRegs[VA.getValNo()];
1216     MVT ArgVT = ArgVTs[VA.getValNo()];
1217
1218     // Handle arg promotion: SExt, ZExt, AExt.
1219     switch (VA.getLocInfo()) {
1220     case CCValAssign::Full:
1221       break;
1222     case CCValAssign::SExt: {
1223       MVT DestVT = VA.getLocVT();
1224       MVT SrcVT = ArgVT;
1225       Arg = EmitIntExt(SrcVT, Arg, DestVT, /*isZExt*/ false);
1226       if (Arg == 0)
1227         return false;
1228       ArgVT = DestVT;
1229       break;
1230     }
1231     case CCValAssign::AExt:
1232     // Intentional fall-through.
1233     case CCValAssign::ZExt: {
1234       MVT DestVT = VA.getLocVT();
1235       MVT SrcVT = ArgVT;
1236       Arg = EmitIntExt(SrcVT, Arg, DestVT, /*isZExt*/ true);
1237       if (Arg == 0)
1238         return false;
1239       ArgVT = DestVT;
1240       break;
1241     }
1242     default:
1243       llvm_unreachable("Unknown arg promotion!");
1244     }
1245
1246     // Now copy/store arg to correct locations.
1247     if (VA.isRegLoc() && !VA.needsCustom()) {
1248       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
1249               TII.get(TargetOpcode::COPY), VA.getLocReg()).addReg(Arg);
1250       RegArgs.push_back(VA.getLocReg());
1251     } else if (VA.needsCustom()) {
1252       // FIXME: Handle custom args.
1253       return false;
1254     } else {
1255       assert(VA.isMemLoc() && "Assuming store on stack.");
1256
1257       // Need to store on the stack.
1258       unsigned ArgSize = VA.getLocVT().getSizeInBits() / 8;
1259
1260       unsigned BEAlign = 0;
1261       if (ArgSize < 8 && !Subtarget->isLittleEndian())
1262         BEAlign = 8 - ArgSize;
1263
1264       Address Addr;
1265       Addr.setKind(Address::RegBase);
1266       Addr.setReg(AArch64::SP);
1267       Addr.setOffset(VA.getLocMemOffset() + BEAlign);
1268
1269       if (!EmitStore(ArgVT, Arg, Addr))
1270         return false;
1271     }
1272   }
1273   return true;
1274 }
1275
1276 bool AArch64FastISel::FinishCall(MVT RetVT, SmallVectorImpl<unsigned> &UsedRegs,
1277                                  const Instruction *I, CallingConv::ID CC,
1278                                  unsigned &NumBytes) {
1279   // Issue CALLSEQ_END
1280   unsigned AdjStackUp = TII.getCallFrameDestroyOpcode();
1281   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AdjStackUp))
1282       .addImm(NumBytes)
1283       .addImm(0);
1284
1285   // Now the return value.
1286   if (RetVT != MVT::isVoid) {
1287     SmallVector<CCValAssign, 16> RVLocs;
1288     CCState CCInfo(CC, false, *FuncInfo.MF, TM, RVLocs, *Context);
1289     CCInfo.AnalyzeCallResult(RetVT, CCAssignFnForCall(CC));
1290
1291     // Only handle a single return value.
1292     if (RVLocs.size() != 1)
1293       return false;
1294
1295     // Copy all of the result registers out of their specified physreg.
1296     MVT CopyVT = RVLocs[0].getValVT();
1297     unsigned ResultReg = createResultReg(TLI.getRegClassFor(CopyVT));
1298     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
1299             TII.get(TargetOpcode::COPY),
1300             ResultReg).addReg(RVLocs[0].getLocReg());
1301     UsedRegs.push_back(RVLocs[0].getLocReg());
1302
1303     // Finally update the result.
1304     UpdateValueMap(I, ResultReg);
1305   }
1306
1307   return true;
1308 }
1309
1310 bool AArch64FastISel::SelectCall(const Instruction *I,
1311                                  const char *IntrMemName = nullptr) {
1312   const CallInst *CI = cast<CallInst>(I);
1313   const Value *Callee = CI->getCalledValue();
1314
1315   // Don't handle inline asm or intrinsics.
1316   if (isa<InlineAsm>(Callee))
1317     return false;
1318
1319   // Only handle global variable Callees.
1320   const GlobalValue *GV = dyn_cast<GlobalValue>(Callee);
1321   if (!GV)
1322     return false;
1323
1324   // Check the calling convention.
1325   ImmutableCallSite CS(CI);
1326   CallingConv::ID CC = CS.getCallingConv();
1327
1328   // Let SDISel handle vararg functions.
1329   PointerType *PT = cast<PointerType>(CS.getCalledValue()->getType());
1330   FunctionType *FTy = cast<FunctionType>(PT->getElementType());
1331   if (FTy->isVarArg())
1332     return false;
1333
1334   // Handle *simple* calls for now.
1335   MVT RetVT;
1336   Type *RetTy = I->getType();
1337   if (RetTy->isVoidTy())
1338     RetVT = MVT::isVoid;
1339   else if (!isTypeLegal(RetTy, RetVT))
1340     return false;
1341
1342   // Set up the argument vectors.
1343   SmallVector<Value *, 8> Args;
1344   SmallVector<unsigned, 8> ArgRegs;
1345   SmallVector<MVT, 8> ArgVTs;
1346   SmallVector<ISD::ArgFlagsTy, 8> ArgFlags;
1347   Args.reserve(CS.arg_size());
1348   ArgRegs.reserve(CS.arg_size());
1349   ArgVTs.reserve(CS.arg_size());
1350   ArgFlags.reserve(CS.arg_size());
1351
1352   for (ImmutableCallSite::arg_iterator i = CS.arg_begin(), e = CS.arg_end();
1353        i != e; ++i) {
1354     // If we're lowering a memory intrinsic instead of a regular call, skip the
1355     // last two arguments, which shouldn't be passed to the underlying function.
1356     if (IntrMemName && e - i <= 2)
1357       break;
1358
1359     unsigned Arg = getRegForValue(*i);
1360     if (Arg == 0)
1361       return false;
1362
1363     ISD::ArgFlagsTy Flags;
1364     unsigned AttrInd = i - CS.arg_begin() + 1;
1365     if (CS.paramHasAttr(AttrInd, Attribute::SExt))
1366       Flags.setSExt();
1367     if (CS.paramHasAttr(AttrInd, Attribute::ZExt))
1368       Flags.setZExt();
1369
1370     // FIXME: Only handle *easy* calls for now.
1371     if (CS.paramHasAttr(AttrInd, Attribute::InReg) ||
1372         CS.paramHasAttr(AttrInd, Attribute::StructRet) ||
1373         CS.paramHasAttr(AttrInd, Attribute::Nest) ||
1374         CS.paramHasAttr(AttrInd, Attribute::ByVal))
1375       return false;
1376
1377     MVT ArgVT;
1378     Type *ArgTy = (*i)->getType();
1379     if (!isTypeLegal(ArgTy, ArgVT) &&
1380         !(ArgVT == MVT::i1 || ArgVT == MVT::i8 || ArgVT == MVT::i16))
1381       return false;
1382
1383     // We don't handle vector parameters yet.
1384     if (ArgVT.isVector() || ArgVT.getSizeInBits() > 64)
1385       return false;
1386
1387     unsigned OriginalAlignment = DL.getABITypeAlignment(ArgTy);
1388     Flags.setOrigAlign(OriginalAlignment);
1389
1390     Args.push_back(*i);
1391     ArgRegs.push_back(Arg);
1392     ArgVTs.push_back(ArgVT);
1393     ArgFlags.push_back(Flags);
1394   }
1395
1396   // Handle the arguments now that we've gotten them.
1397   SmallVector<unsigned, 4> RegArgs;
1398   unsigned NumBytes;
1399   if (!ProcessCallArgs(Args, ArgRegs, ArgVTs, ArgFlags, RegArgs, CC, NumBytes))
1400     return false;
1401
1402   // Issue the call.
1403   MachineInstrBuilder MIB;
1404   MIB = BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::BL));
1405   if (!IntrMemName)
1406     MIB.addGlobalAddress(GV, 0, 0);
1407   else
1408     MIB.addExternalSymbol(IntrMemName, 0);
1409
1410   // Add implicit physical register uses to the call.
1411   for (unsigned i = 0, e = RegArgs.size(); i != e; ++i)
1412     MIB.addReg(RegArgs[i], RegState::Implicit);
1413
1414   // Add a register mask with the call-preserved registers.
1415   // Proper defs for return values will be added by setPhysRegsDeadExcept().
1416   MIB.addRegMask(TRI.getCallPreservedMask(CS.getCallingConv()));
1417
1418   // Finish off the call including any return values.
1419   SmallVector<unsigned, 4> UsedRegs;
1420   if (!FinishCall(RetVT, UsedRegs, I, CC, NumBytes))
1421     return false;
1422
1423   // Set all unused physreg defs as dead.
1424   static_cast<MachineInstr *>(MIB)->setPhysRegsDeadExcept(UsedRegs, TRI);
1425
1426   return true;
1427 }
1428
1429 bool AArch64FastISel::IsMemCpySmall(uint64_t Len, unsigned Alignment) {
1430   if (Alignment)
1431     return Len / Alignment <= 4;
1432   else
1433     return Len < 32;
1434 }
1435
1436 bool AArch64FastISel::TryEmitSmallMemCpy(Address Dest, Address Src,
1437                                          uint64_t Len, unsigned Alignment) {
1438   // Make sure we don't bloat code by inlining very large memcpy's.
1439   if (!IsMemCpySmall(Len, Alignment))
1440     return false;
1441
1442   int64_t UnscaledOffset = 0;
1443   Address OrigDest = Dest;
1444   Address OrigSrc = Src;
1445
1446   while (Len) {
1447     MVT VT;
1448     if (!Alignment || Alignment >= 8) {
1449       if (Len >= 8)
1450         VT = MVT::i64;
1451       else if (Len >= 4)
1452         VT = MVT::i32;
1453       else if (Len >= 2)
1454         VT = MVT::i16;
1455       else {
1456         VT = MVT::i8;
1457       }
1458     } else {
1459       // Bound based on alignment.
1460       if (Len >= 4 && Alignment == 4)
1461         VT = MVT::i32;
1462       else if (Len >= 2 && Alignment == 2)
1463         VT = MVT::i16;
1464       else {
1465         VT = MVT::i8;
1466       }
1467     }
1468
1469     bool RV;
1470     unsigned ResultReg;
1471     RV = EmitLoad(VT, ResultReg, Src);
1472     assert(RV == true && "Should be able to handle this load.");
1473     RV = EmitStore(VT, ResultReg, Dest);
1474     assert(RV == true && "Should be able to handle this store.");
1475     (void)RV;
1476
1477     int64_t Size = VT.getSizeInBits() / 8;
1478     Len -= Size;
1479     UnscaledOffset += Size;
1480
1481     // We need to recompute the unscaled offset for each iteration.
1482     Dest.setOffset(OrigDest.getOffset() + UnscaledOffset);
1483     Src.setOffset(OrigSrc.getOffset() + UnscaledOffset);
1484   }
1485
1486   return true;
1487 }
1488
1489 bool AArch64FastISel::SelectIntrinsicCall(const IntrinsicInst &I) {
1490   // FIXME: Handle more intrinsics.
1491   switch (I.getIntrinsicID()) {
1492   default:
1493     return false;
1494   case Intrinsic::memcpy:
1495   case Intrinsic::memmove: {
1496     const MemTransferInst &MTI = cast<MemTransferInst>(I);
1497     // Don't handle volatile.
1498     if (MTI.isVolatile())
1499       return false;
1500
1501     // Disable inlining for memmove before calls to ComputeAddress.  Otherwise,
1502     // we would emit dead code because we don't currently handle memmoves.
1503     bool isMemCpy = (I.getIntrinsicID() == Intrinsic::memcpy);
1504     if (isa<ConstantInt>(MTI.getLength()) && isMemCpy) {
1505       // Small memcpy's are common enough that we want to do them without a call
1506       // if possible.
1507       uint64_t Len = cast<ConstantInt>(MTI.getLength())->getZExtValue();
1508       unsigned Alignment = MTI.getAlignment();
1509       if (IsMemCpySmall(Len, Alignment)) {
1510         Address Dest, Src;
1511         if (!ComputeAddress(MTI.getRawDest(), Dest) ||
1512             !ComputeAddress(MTI.getRawSource(), Src))
1513           return false;
1514         if (TryEmitSmallMemCpy(Dest, Src, Len, Alignment))
1515           return true;
1516       }
1517     }
1518
1519     if (!MTI.getLength()->getType()->isIntegerTy(64))
1520       return false;
1521
1522     if (MTI.getSourceAddressSpace() > 255 || MTI.getDestAddressSpace() > 255)
1523       // Fast instruction selection doesn't support the special
1524       // address spaces.
1525       return false;
1526
1527     const char *IntrMemName = isa<MemCpyInst>(I) ? "memcpy" : "memmove";
1528     return SelectCall(&I, IntrMemName);
1529   }
1530   case Intrinsic::memset: {
1531     const MemSetInst &MSI = cast<MemSetInst>(I);
1532     // Don't handle volatile.
1533     if (MSI.isVolatile())
1534       return false;
1535
1536     if (!MSI.getLength()->getType()->isIntegerTy(64))
1537       return false;
1538
1539     if (MSI.getDestAddressSpace() > 255)
1540       // Fast instruction selection doesn't support the special
1541       // address spaces.
1542       return false;
1543
1544     return SelectCall(&I, "memset");
1545   }
1546   case Intrinsic::trap: {
1547     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::BRK))
1548         .addImm(1);
1549     return true;
1550   }
1551   }
1552   return false;
1553 }
1554
1555 bool AArch64FastISel::SelectRet(const Instruction *I) {
1556   const ReturnInst *Ret = cast<ReturnInst>(I);
1557   const Function &F = *I->getParent()->getParent();
1558
1559   if (!FuncInfo.CanLowerReturn)
1560     return false;
1561
1562   if (F.isVarArg())
1563     return false;
1564
1565   // Build a list of return value registers.
1566   SmallVector<unsigned, 4> RetRegs;
1567
1568   if (Ret->getNumOperands() > 0) {
1569     CallingConv::ID CC = F.getCallingConv();
1570     SmallVector<ISD::OutputArg, 4> Outs;
1571     GetReturnInfo(F.getReturnType(), F.getAttributes(), Outs, TLI);
1572
1573     // Analyze operands of the call, assigning locations to each operand.
1574     SmallVector<CCValAssign, 16> ValLocs;
1575     CCState CCInfo(CC, F.isVarArg(), *FuncInfo.MF, TM, ValLocs,
1576                    I->getContext());
1577     CCAssignFn *RetCC = CC == CallingConv::WebKit_JS ? RetCC_AArch64_WebKit_JS
1578                                                      : RetCC_AArch64_AAPCS;
1579     CCInfo.AnalyzeReturn(Outs, RetCC);
1580
1581     // Only handle a single return value for now.
1582     if (ValLocs.size() != 1)
1583       return false;
1584
1585     CCValAssign &VA = ValLocs[0];
1586     const Value *RV = Ret->getOperand(0);
1587
1588     // Don't bother handling odd stuff for now.
1589     if (VA.getLocInfo() != CCValAssign::Full)
1590       return false;
1591     // Only handle register returns for now.
1592     if (!VA.isRegLoc())
1593       return false;
1594     unsigned Reg = getRegForValue(RV);
1595     if (Reg == 0)
1596       return false;
1597
1598     unsigned SrcReg = Reg + VA.getValNo();
1599     unsigned DestReg = VA.getLocReg();
1600     // Avoid a cross-class copy. This is very unlikely.
1601     if (!MRI.getRegClass(SrcReg)->contains(DestReg))
1602       return false;
1603
1604     EVT RVEVT = TLI.getValueType(RV->getType());
1605     if (!RVEVT.isSimple())
1606       return false;
1607
1608     // Vectors (of > 1 lane) in big endian need tricky handling.
1609     if (RVEVT.isVector() && RVEVT.getVectorNumElements() > 1)
1610       return false;
1611
1612     MVT RVVT = RVEVT.getSimpleVT();
1613     if (RVVT == MVT::f128)
1614       return false;
1615     MVT DestVT = VA.getValVT();
1616     // Special handling for extended integers.
1617     if (RVVT != DestVT) {
1618       if (RVVT != MVT::i1 && RVVT != MVT::i8 && RVVT != MVT::i16)
1619         return false;
1620
1621       if (!Outs[0].Flags.isZExt() && !Outs[0].Flags.isSExt())
1622         return false;
1623
1624       bool isZExt = Outs[0].Flags.isZExt();
1625       SrcReg = EmitIntExt(RVVT, SrcReg, DestVT, isZExt);
1626       if (SrcReg == 0)
1627         return false;
1628     }
1629
1630     // Make the copy.
1631     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
1632             TII.get(TargetOpcode::COPY), DestReg).addReg(SrcReg);
1633
1634     // Add register to return instruction.
1635     RetRegs.push_back(VA.getLocReg());
1636   }
1637
1638   MachineInstrBuilder MIB = BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
1639                                     TII.get(AArch64::RET_ReallyLR));
1640   for (unsigned i = 0, e = RetRegs.size(); i != e; ++i)
1641     MIB.addReg(RetRegs[i], RegState::Implicit);
1642   return true;
1643 }
1644
1645 bool AArch64FastISel::SelectTrunc(const Instruction *I) {
1646   Type *DestTy = I->getType();
1647   Value *Op = I->getOperand(0);
1648   Type *SrcTy = Op->getType();
1649
1650   EVT SrcEVT = TLI.getValueType(SrcTy, true);
1651   EVT DestEVT = TLI.getValueType(DestTy, true);
1652   if (!SrcEVT.isSimple())
1653     return false;
1654   if (!DestEVT.isSimple())
1655     return false;
1656
1657   MVT SrcVT = SrcEVT.getSimpleVT();
1658   MVT DestVT = DestEVT.getSimpleVT();
1659
1660   if (SrcVT != MVT::i64 && SrcVT != MVT::i32 && SrcVT != MVT::i16 &&
1661       SrcVT != MVT::i8)
1662     return false;
1663   if (DestVT != MVT::i32 && DestVT != MVT::i16 && DestVT != MVT::i8 &&
1664       DestVT != MVT::i1)
1665     return false;
1666
1667   unsigned SrcReg = getRegForValue(Op);
1668   if (!SrcReg)
1669     return false;
1670
1671   // If we're truncating from i64 to a smaller non-legal type then generate an
1672   // AND.  Otherwise, we know the high bits are undefined and a truncate doesn't
1673   // generate any code.
1674   if (SrcVT == MVT::i64) {
1675     uint64_t Mask = 0;
1676     switch (DestVT.SimpleTy) {
1677     default:
1678       // Trunc i64 to i32 is handled by the target-independent fast-isel.
1679       return false;
1680     case MVT::i1:
1681       Mask = 0x1;
1682       break;
1683     case MVT::i8:
1684       Mask = 0xff;
1685       break;
1686     case MVT::i16:
1687       Mask = 0xffff;
1688       break;
1689     }
1690     // Issue an extract_subreg to get the lower 32-bits.
1691     unsigned Reg32 = FastEmitInst_extractsubreg(MVT::i32, SrcReg, /*Kill=*/true,
1692                                                 AArch64::sub_32);
1693     MRI.constrainRegClass(Reg32, &AArch64::GPR32RegClass);
1694     // Create the AND instruction which performs the actual truncation.
1695     unsigned ANDReg = createResultReg(&AArch64::GPR32spRegClass);
1696     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ANDWri),
1697             ANDReg)
1698         .addReg(Reg32)
1699         .addImm(AArch64_AM::encodeLogicalImmediate(Mask, 32));
1700     SrcReg = ANDReg;
1701   }
1702
1703   UpdateValueMap(I, SrcReg);
1704   return true;
1705 }
1706
1707 unsigned AArch64FastISel::Emiti1Ext(unsigned SrcReg, MVT DestVT, bool isZExt) {
1708   assert((DestVT == MVT::i8 || DestVT == MVT::i16 || DestVT == MVT::i32 ||
1709           DestVT == MVT::i64) &&
1710          "Unexpected value type.");
1711   // Handle i8 and i16 as i32.
1712   if (DestVT == MVT::i8 || DestVT == MVT::i16)
1713     DestVT = MVT::i32;
1714
1715   if (isZExt) {
1716     MRI.constrainRegClass(SrcReg, &AArch64::GPR32RegClass);
1717     unsigned ResultReg = createResultReg(&AArch64::GPR32spRegClass);
1718     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::ANDWri),
1719             ResultReg)
1720         .addReg(SrcReg)
1721         .addImm(AArch64_AM::encodeLogicalImmediate(1, 32));
1722
1723     if (DestVT == MVT::i64) {
1724       // We're ZExt i1 to i64.  The ANDWri Wd, Ws, #1 implicitly clears the
1725       // upper 32 bits.  Emit a SUBREG_TO_REG to extend from Wd to Xd.
1726       unsigned Reg64 = MRI.createVirtualRegister(&AArch64::GPR64RegClass);
1727       BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
1728               TII.get(AArch64::SUBREG_TO_REG), Reg64)
1729           .addImm(0)
1730           .addReg(ResultReg)
1731           .addImm(AArch64::sub_32);
1732       ResultReg = Reg64;
1733     }
1734     return ResultReg;
1735   } else {
1736     if (DestVT == MVT::i64) {
1737       // FIXME: We're SExt i1 to i64.
1738       return 0;
1739     }
1740     unsigned ResultReg = createResultReg(&AArch64::GPR32RegClass);
1741     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(AArch64::SBFMWri),
1742             ResultReg)
1743         .addReg(SrcReg)
1744         .addImm(0)
1745         .addImm(0);
1746     return ResultReg;
1747   }
1748 }
1749
1750 unsigned AArch64FastISel::EmitIntExt(MVT SrcVT, unsigned SrcReg, MVT DestVT,
1751                                      bool isZExt) {
1752   assert(DestVT != MVT::i1 && "ZeroExt/SignExt an i1?");
1753   unsigned Opc;
1754   unsigned Imm = 0;
1755
1756   switch (SrcVT.SimpleTy) {
1757   default:
1758     return 0;
1759   case MVT::i1:
1760     return Emiti1Ext(SrcReg, DestVT, isZExt);
1761   case MVT::i8:
1762     if (DestVT == MVT::i64)
1763       Opc = isZExt ? AArch64::UBFMXri : AArch64::SBFMXri;
1764     else
1765       Opc = isZExt ? AArch64::UBFMWri : AArch64::SBFMWri;
1766     Imm = 7;
1767     break;
1768   case MVT::i16:
1769     if (DestVT == MVT::i64)
1770       Opc = isZExt ? AArch64::UBFMXri : AArch64::SBFMXri;
1771     else
1772       Opc = isZExt ? AArch64::UBFMWri : AArch64::SBFMWri;
1773     Imm = 15;
1774     break;
1775   case MVT::i32:
1776     assert(DestVT == MVT::i64 && "IntExt i32 to i32?!?");
1777     Opc = isZExt ? AArch64::UBFMXri : AArch64::SBFMXri;
1778     Imm = 31;
1779     break;
1780   }
1781
1782   // Handle i8 and i16 as i32.
1783   if (DestVT == MVT::i8 || DestVT == MVT::i16)
1784     DestVT = MVT::i32;
1785   else if (DestVT == MVT::i64) {
1786     unsigned Src64 = MRI.createVirtualRegister(&AArch64::GPR64RegClass);
1787     BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc,
1788             TII.get(AArch64::SUBREG_TO_REG), Src64)
1789         .addImm(0)
1790         .addReg(SrcReg)
1791         .addImm(AArch64::sub_32);
1792     SrcReg = Src64;
1793   }
1794
1795   unsigned ResultReg = createResultReg(TLI.getRegClassFor(DestVT));
1796   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(Opc), ResultReg)
1797       .addReg(SrcReg)
1798       .addImm(0)
1799       .addImm(Imm);
1800
1801   return ResultReg;
1802 }
1803
1804 bool AArch64FastISel::SelectIntExt(const Instruction *I) {
1805   // On ARM, in general, integer casts don't involve legal types; this code
1806   // handles promotable integers.  The high bits for a type smaller than
1807   // the register size are assumed to be undefined.
1808   Type *DestTy = I->getType();
1809   Value *Src = I->getOperand(0);
1810   Type *SrcTy = Src->getType();
1811
1812   bool isZExt = isa<ZExtInst>(I);
1813   unsigned SrcReg = getRegForValue(Src);
1814   if (!SrcReg)
1815     return false;
1816
1817   EVT SrcEVT = TLI.getValueType(SrcTy, true);
1818   EVT DestEVT = TLI.getValueType(DestTy, true);
1819   if (!SrcEVT.isSimple())
1820     return false;
1821   if (!DestEVT.isSimple())
1822     return false;
1823
1824   MVT SrcVT = SrcEVT.getSimpleVT();
1825   MVT DestVT = DestEVT.getSimpleVT();
1826   unsigned ResultReg = EmitIntExt(SrcVT, SrcReg, DestVT, isZExt);
1827   if (ResultReg == 0)
1828     return false;
1829   UpdateValueMap(I, ResultReg);
1830   return true;
1831 }
1832
1833 bool AArch64FastISel::SelectRem(const Instruction *I, unsigned ISDOpcode) {
1834   EVT DestEVT = TLI.getValueType(I->getType(), true);
1835   if (!DestEVT.isSimple())
1836     return false;
1837
1838   MVT DestVT = DestEVT.getSimpleVT();
1839   if (DestVT != MVT::i64 && DestVT != MVT::i32)
1840     return false;
1841
1842   unsigned DivOpc;
1843   bool is64bit = (DestVT == MVT::i64);
1844   switch (ISDOpcode) {
1845   default:
1846     return false;
1847   case ISD::SREM:
1848     DivOpc = is64bit ? AArch64::SDIVXr : AArch64::SDIVWr;
1849     break;
1850   case ISD::UREM:
1851     DivOpc = is64bit ? AArch64::UDIVXr : AArch64::UDIVWr;
1852     break;
1853   }
1854   unsigned MSubOpc = is64bit ? AArch64::MSUBXrrr : AArch64::MSUBWrrr;
1855   unsigned Src0Reg = getRegForValue(I->getOperand(0));
1856   if (!Src0Reg)
1857     return false;
1858
1859   unsigned Src1Reg = getRegForValue(I->getOperand(1));
1860   if (!Src1Reg)
1861     return false;
1862
1863   unsigned QuotReg = createResultReg(TLI.getRegClassFor(DestVT));
1864   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(DivOpc), QuotReg)
1865       .addReg(Src0Reg)
1866       .addReg(Src1Reg);
1867   // The remainder is computed as numerator - (quotient * denominator) using the
1868   // MSUB instruction.
1869   unsigned ResultReg = createResultReg(TLI.getRegClassFor(DestVT));
1870   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(MSubOpc), ResultReg)
1871       .addReg(QuotReg)
1872       .addReg(Src1Reg)
1873       .addReg(Src0Reg);
1874   UpdateValueMap(I, ResultReg);
1875   return true;
1876 }
1877
1878 bool AArch64FastISel::SelectMul(const Instruction *I) {
1879   EVT SrcEVT = TLI.getValueType(I->getOperand(0)->getType(), true);
1880   if (!SrcEVT.isSimple())
1881     return false;
1882   MVT SrcVT = SrcEVT.getSimpleVT();
1883
1884   // Must be simple value type.  Don't handle vectors.
1885   if (SrcVT != MVT::i64 && SrcVT != MVT::i32 && SrcVT != MVT::i16 &&
1886       SrcVT != MVT::i8)
1887     return false;
1888
1889   unsigned Opc;
1890   unsigned ZReg;
1891   switch (SrcVT.SimpleTy) {
1892   default:
1893     return false;
1894   case MVT::i8:
1895   case MVT::i16:
1896   case MVT::i32:
1897     ZReg = AArch64::WZR;
1898     Opc = AArch64::MADDWrrr;
1899     break;
1900   case MVT::i64:
1901     ZReg = AArch64::XZR;
1902     Opc = AArch64::MADDXrrr;
1903     break;
1904   }
1905
1906   unsigned Src0Reg = getRegForValue(I->getOperand(0));
1907   if (!Src0Reg)
1908     return false;
1909
1910   unsigned Src1Reg = getRegForValue(I->getOperand(1));
1911   if (!Src1Reg)
1912     return false;
1913
1914   // Create the base instruction, then add the operands.
1915   unsigned ResultReg = createResultReg(TLI.getRegClassFor(SrcVT));
1916   BuildMI(*FuncInfo.MBB, FuncInfo.InsertPt, DbgLoc, TII.get(Opc), ResultReg)
1917       .addReg(Src0Reg)
1918       .addReg(Src1Reg)
1919       .addReg(ZReg);
1920   UpdateValueMap(I, ResultReg);
1921   return true;
1922 }
1923
1924 bool AArch64FastISel::TargetSelectInstruction(const Instruction *I) {
1925   switch (I->getOpcode()) {
1926   default:
1927     break;
1928   case Instruction::Load:
1929     return SelectLoad(I);
1930   case Instruction::Store:
1931     return SelectStore(I);
1932   case Instruction::Br:
1933     return SelectBranch(I);
1934   case Instruction::IndirectBr:
1935     return SelectIndirectBr(I);
1936   case Instruction::FCmp:
1937   case Instruction::ICmp:
1938     return SelectCmp(I);
1939   case Instruction::Select:
1940     return SelectSelect(I);
1941   case Instruction::FPExt:
1942     return SelectFPExt(I);
1943   case Instruction::FPTrunc:
1944     return SelectFPTrunc(I);
1945   case Instruction::FPToSI:
1946     return SelectFPToInt(I, /*Signed=*/true);
1947   case Instruction::FPToUI:
1948     return SelectFPToInt(I, /*Signed=*/false);
1949   case Instruction::SIToFP:
1950     return SelectIntToFP(I, /*Signed=*/true);
1951   case Instruction::UIToFP:
1952     return SelectIntToFP(I, /*Signed=*/false);
1953   case Instruction::SRem:
1954     return SelectRem(I, ISD::SREM);
1955   case Instruction::URem:
1956     return SelectRem(I, ISD::UREM);
1957   case Instruction::Call:
1958     if (const IntrinsicInst *II = dyn_cast<IntrinsicInst>(I))
1959       return SelectIntrinsicCall(*II);
1960     return SelectCall(I);
1961   case Instruction::Ret:
1962     return SelectRet(I);
1963   case Instruction::Trunc:
1964     return SelectTrunc(I);
1965   case Instruction::ZExt:
1966   case Instruction::SExt:
1967     return SelectIntExt(I);
1968   case Instruction::Mul:
1969     // FIXME: This really should be handled by the target-independent selector.
1970     return SelectMul(I);
1971   }
1972   return false;
1973   // Silence warnings.
1974   (void)&CC_AArch64_DarwinPCS_VarArg;
1975 }
1976
1977 namespace llvm {
1978 llvm::FastISel *AArch64::createFastISel(FunctionLoweringInfo &funcInfo,
1979                                         const TargetLibraryInfo *libInfo) {
1980   return new AArch64FastISel(funcInfo, libInfo);
1981 }
1982 }