PPCFrameLowering.cpp revision 270147
1234353Sdim//===-- PPCFrameLowering.cpp - PPC Frame Information ----------------------===//
2218885Sdim//
3218885Sdim//                     The LLVM Compiler Infrastructure
4218885Sdim//
5218885Sdim// This file is distributed under the University of Illinois Open Source
6218885Sdim// License. See LICENSE.TXT for details.
7218885Sdim//
8218885Sdim//===----------------------------------------------------------------------===//
9218885Sdim//
10218885Sdim// This file contains the PPC implementation of TargetFrameLowering class.
11218885Sdim//
12218885Sdim//===----------------------------------------------------------------------===//
13218885Sdim
14218885Sdim#include "PPCFrameLowering.h"
15249423Sdim#include "PPCInstrBuilder.h"
16218885Sdim#include "PPCInstrInfo.h"
17218885Sdim#include "PPCMachineFunctionInfo.h"
18218885Sdim#include "llvm/CodeGen/MachineFrameInfo.h"
19218885Sdim#include "llvm/CodeGen/MachineFunction.h"
20218885Sdim#include "llvm/CodeGen/MachineInstrBuilder.h"
21218885Sdim#include "llvm/CodeGen/MachineModuleInfo.h"
22218885Sdim#include "llvm/CodeGen/MachineRegisterInfo.h"
23218885Sdim#include "llvm/CodeGen/RegisterScavenging.h"
24249423Sdim#include "llvm/IR/Function.h"
25218885Sdim#include "llvm/Target/TargetOptions.h"
26218885Sdim
27218885Sdimusing namespace llvm;
28218885Sdim
29218885Sdim/// VRRegNo - Map from a numbered VR register to its enum value.
30218885Sdim///
31234353Sdimstatic const uint16_t VRRegNo[] = {
32218885Sdim PPC::V0 , PPC::V1 , PPC::V2 , PPC::V3 , PPC::V4 , PPC::V5 , PPC::V6 , PPC::V7 ,
33218885Sdim PPC::V8 , PPC::V9 , PPC::V10, PPC::V11, PPC::V12, PPC::V13, PPC::V14, PPC::V15,
34218885Sdim PPC::V16, PPC::V17, PPC::V18, PPC::V19, PPC::V20, PPC::V21, PPC::V22, PPC::V23,
35218885Sdim PPC::V24, PPC::V25, PPC::V26, PPC::V27, PPC::V28, PPC::V29, PPC::V30, PPC::V31
36218885Sdim};
37218885Sdim
38218885Sdim/// RemoveVRSaveCode - We have found that this function does not need any code
39218885Sdim/// to manipulate the VRSAVE register, even though it uses vector registers.
40218885Sdim/// This can happen when the only registers used are known to be live in or out
41218885Sdim/// of the function.  Remove all of the VRSAVE related code from the function.
42243830Sdim/// FIXME: The removal of the code results in a compile failure at -O0 when the
43243830Sdim/// function contains a function call, as the GPR containing original VRSAVE
44243830Sdim/// contents is spilled and reloaded around the call.  Without the prolog code,
45243830Sdim/// the spill instruction refers to an undefined register.  This code needs
46243830Sdim/// to account for all uses of that GPR.
47218885Sdimstatic void RemoveVRSaveCode(MachineInstr *MI) {
48218885Sdim  MachineBasicBlock *Entry = MI->getParent();
49218885Sdim  MachineFunction *MF = Entry->getParent();
50218885Sdim
51218885Sdim  // We know that the MTVRSAVE instruction immediately follows MI.  Remove it.
52218885Sdim  MachineBasicBlock::iterator MBBI = MI;
53218885Sdim  ++MBBI;
54218885Sdim  assert(MBBI != Entry->end() && MBBI->getOpcode() == PPC::MTVRSAVE);
55218885Sdim  MBBI->eraseFromParent();
56218885Sdim
57218885Sdim  bool RemovedAllMTVRSAVEs = true;
58218885Sdim  // See if we can find and remove the MTVRSAVE instruction from all of the
59218885Sdim  // epilog blocks.
60218885Sdim  for (MachineFunction::iterator I = MF->begin(), E = MF->end(); I != E; ++I) {
61218885Sdim    // If last instruction is a return instruction, add an epilogue
62234353Sdim    if (!I->empty() && I->back().isReturn()) {
63218885Sdim      bool FoundIt = false;
64218885Sdim      for (MBBI = I->end(); MBBI != I->begin(); ) {
65218885Sdim        --MBBI;
66218885Sdim        if (MBBI->getOpcode() == PPC::MTVRSAVE) {
67218885Sdim          MBBI->eraseFromParent();  // remove it.
68218885Sdim          FoundIt = true;
69218885Sdim          break;
70218885Sdim        }
71218885Sdim      }
72218885Sdim      RemovedAllMTVRSAVEs &= FoundIt;
73218885Sdim    }
74218885Sdim  }
75218885Sdim
76218885Sdim  // If we found and removed all MTVRSAVE instructions, remove the read of
77218885Sdim  // VRSAVE as well.
78218885Sdim  if (RemovedAllMTVRSAVEs) {
79218885Sdim    MBBI = MI;
80218885Sdim    assert(MBBI != Entry->begin() && "UPDATE_VRSAVE is first instr in block?");
81218885Sdim    --MBBI;
82218885Sdim    assert(MBBI->getOpcode() == PPC::MFVRSAVE && "VRSAVE instrs wandered?");
83218885Sdim    MBBI->eraseFromParent();
84218885Sdim  }
85218885Sdim
86218885Sdim  // Finally, nuke the UPDATE_VRSAVE.
87218885Sdim  MI->eraseFromParent();
88218885Sdim}
89218885Sdim
90218885Sdim// HandleVRSaveUpdate - MI is the UPDATE_VRSAVE instruction introduced by the
91218885Sdim// instruction selector.  Based on the vector registers that have been used,
92218885Sdim// transform this into the appropriate ORI instruction.
93218885Sdimstatic void HandleVRSaveUpdate(MachineInstr *MI, const TargetInstrInfo &TII) {
94218885Sdim  MachineFunction *MF = MI->getParent()->getParent();
95249423Sdim  const TargetRegisterInfo *TRI = MF->getTarget().getRegisterInfo();
96218885Sdim  DebugLoc dl = MI->getDebugLoc();
97218885Sdim
98218885Sdim  unsigned UsedRegMask = 0;
99218885Sdim  for (unsigned i = 0; i != 32; ++i)
100218885Sdim    if (MF->getRegInfo().isPhysRegUsed(VRRegNo[i]))
101218885Sdim      UsedRegMask |= 1 << (31-i);
102218885Sdim
103218885Sdim  // Live in and live out values already must be in the mask, so don't bother
104218885Sdim  // marking them.
105218885Sdim  for (MachineRegisterInfo::livein_iterator
106218885Sdim       I = MF->getRegInfo().livein_begin(),
107218885Sdim       E = MF->getRegInfo().livein_end(); I != E; ++I) {
108249423Sdim    unsigned RegNo = TRI->getEncodingValue(I->first);
109218885Sdim    if (VRRegNo[RegNo] == I->first)        // If this really is a vector reg.
110218885Sdim      UsedRegMask &= ~(1 << (31-RegNo));   // Doesn't need to be marked.
111218885Sdim  }
112249423Sdim
113249423Sdim  // Live out registers appear as use operands on return instructions.
114249423Sdim  for (MachineFunction::const_iterator BI = MF->begin(), BE = MF->end();
115249423Sdim       UsedRegMask != 0 && BI != BE; ++BI) {
116249423Sdim    const MachineBasicBlock &MBB = *BI;
117249423Sdim    if (MBB.empty() || !MBB.back().isReturn())
118249423Sdim      continue;
119249423Sdim    const MachineInstr &Ret = MBB.back();
120249423Sdim    for (unsigned I = 0, E = Ret.getNumOperands(); I != E; ++I) {
121249423Sdim      const MachineOperand &MO = Ret.getOperand(I);
122249423Sdim      if (!MO.isReg() || !PPC::VRRCRegClass.contains(MO.getReg()))
123249423Sdim        continue;
124249423Sdim      unsigned RegNo = TRI->getEncodingValue(MO.getReg());
125249423Sdim      UsedRegMask &= ~(1 << (31-RegNo));
126249423Sdim    }
127218885Sdim  }
128218885Sdim
129218885Sdim  // If no registers are used, turn this into a copy.
130218885Sdim  if (UsedRegMask == 0) {
131218885Sdim    // Remove all VRSAVE code.
132218885Sdim    RemoveVRSaveCode(MI);
133218885Sdim    return;
134218885Sdim  }
135218885Sdim
136218885Sdim  unsigned SrcReg = MI->getOperand(1).getReg();
137218885Sdim  unsigned DstReg = MI->getOperand(0).getReg();
138218885Sdim
139218885Sdim  if ((UsedRegMask & 0xFFFF) == UsedRegMask) {
140218885Sdim    if (DstReg != SrcReg)
141218885Sdim      BuildMI(*MI->getParent(), MI, dl, TII.get(PPC::ORI), DstReg)
142218885Sdim        .addReg(SrcReg)
143218885Sdim        .addImm(UsedRegMask);
144218885Sdim    else
145218885Sdim      BuildMI(*MI->getParent(), MI, dl, TII.get(PPC::ORI), DstReg)
146218885Sdim        .addReg(SrcReg, RegState::Kill)
147218885Sdim        .addImm(UsedRegMask);
148218885Sdim  } else if ((UsedRegMask & 0xFFFF0000) == UsedRegMask) {
149218885Sdim    if (DstReg != SrcReg)
150218885Sdim      BuildMI(*MI->getParent(), MI, dl, TII.get(PPC::ORIS), DstReg)
151218885Sdim        .addReg(SrcReg)
152218885Sdim        .addImm(UsedRegMask >> 16);
153218885Sdim    else
154218885Sdim      BuildMI(*MI->getParent(), MI, dl, TII.get(PPC::ORIS), DstReg)
155218885Sdim        .addReg(SrcReg, RegState::Kill)
156218885Sdim        .addImm(UsedRegMask >> 16);
157218885Sdim  } else {
158218885Sdim    if (DstReg != SrcReg)
159218885Sdim      BuildMI(*MI->getParent(), MI, dl, TII.get(PPC::ORIS), DstReg)
160218885Sdim        .addReg(SrcReg)
161218885Sdim        .addImm(UsedRegMask >> 16);
162218885Sdim    else
163218885Sdim      BuildMI(*MI->getParent(), MI, dl, TII.get(PPC::ORIS), DstReg)
164218885Sdim        .addReg(SrcReg, RegState::Kill)
165218885Sdim        .addImm(UsedRegMask >> 16);
166218885Sdim
167218885Sdim    BuildMI(*MI->getParent(), MI, dl, TII.get(PPC::ORI), DstReg)
168218885Sdim      .addReg(DstReg, RegState::Kill)
169218885Sdim      .addImm(UsedRegMask & 0xFFFF);
170218885Sdim  }
171218885Sdim
172218885Sdim  // Remove the old UPDATE_VRSAVE instruction.
173218885Sdim  MI->eraseFromParent();
174218885Sdim}
175218885Sdim
176243830Sdimstatic bool spillsCR(const MachineFunction &MF) {
177243830Sdim  const PPCFunctionInfo *FuncInfo = MF.getInfo<PPCFunctionInfo>();
178243830Sdim  return FuncInfo->isCRSpilled();
179243830Sdim}
180243830Sdim
181249423Sdimstatic bool spillsVRSAVE(const MachineFunction &MF) {
182249423Sdim  const PPCFunctionInfo *FuncInfo = MF.getInfo<PPCFunctionInfo>();
183249423Sdim  return FuncInfo->isVRSAVESpilled();
184249423Sdim}
185249423Sdim
186249423Sdimstatic bool hasSpills(const MachineFunction &MF) {
187249423Sdim  const PPCFunctionInfo *FuncInfo = MF.getInfo<PPCFunctionInfo>();
188249423Sdim  return FuncInfo->hasSpills();
189249423Sdim}
190249423Sdim
191249423Sdimstatic bool hasNonRISpills(const MachineFunction &MF) {
192249423Sdim  const PPCFunctionInfo *FuncInfo = MF.getInfo<PPCFunctionInfo>();
193249423Sdim  return FuncInfo->hasNonRISpills();
194249423Sdim}
195249423Sdim
196218885Sdim/// determineFrameLayout - Determine the size of the frame and maximum call
197218885Sdim/// frame size.
198249423Sdimunsigned PPCFrameLowering::determineFrameLayout(MachineFunction &MF,
199249423Sdim                                                bool UpdateMF,
200249423Sdim                                                bool UseEstimate) const {
201218885Sdim  MachineFrameInfo *MFI = MF.getFrameInfo();
202218885Sdim
203218885Sdim  // Get the number of bytes to allocate from the FrameInfo
204249423Sdim  unsigned FrameSize =
205249423Sdim    UseEstimate ? MFI->estimateStackSize(MF) : MFI->getStackSize();
206218885Sdim
207261991Sdim  // Get stack alignments. The frame must be aligned to the greatest of these:
208261991Sdim  unsigned TargetAlign = getStackAlignment(); // alignment required per the ABI
209261991Sdim  unsigned MaxAlign = MFI->getMaxAlignment(); // algmt required by data in frame
210261991Sdim  unsigned AlignMask = std::max(MaxAlign, TargetAlign) - 1;
211218885Sdim
212261991Sdim  const PPCRegisterInfo *RegInfo =
213261991Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
214261991Sdim
215218885Sdim  // If we are a leaf function, and use up to 224 bytes of stack space,
216218885Sdim  // don't have a frame pointer, calls, or dynamic alloca then we do not need
217251662Sdim  // to adjust the stack pointer (we fit in the Red Zone).
218249423Sdim  // The 32-bit SVR4 ABI has no Red Zone. However, it can still generate
219249423Sdim  // stackless code if all local vars are reg-allocated.
220249423Sdim  bool DisableRedZone = MF.getFunction()->getAttributes().
221249423Sdim    hasAttribute(AttributeSet::FunctionIndex, Attribute::NoRedZone);
222218885Sdim  if (!DisableRedZone &&
223249423Sdim      (Subtarget.isPPC64() ||                      // 32-bit SVR4, no stack-
224249423Sdim       !Subtarget.isSVR4ABI() ||                   //   allocated locals.
225249423Sdim	FrameSize == 0) &&
226218885Sdim      FrameSize <= 224 &&                          // Fits in red zone.
227218885Sdim      !MFI->hasVarSizedObjects() &&                // No dynamic alloca.
228218885Sdim      !MFI->adjustsStack() &&                      // No calls.
229261991Sdim      !RegInfo->hasBasePointer(MF)) { // No special alignment.
230218885Sdim    // No need for frame
231249423Sdim    if (UpdateMF)
232249423Sdim      MFI->setStackSize(0);
233249423Sdim    return 0;
234218885Sdim  }
235218885Sdim
236218885Sdim  // Get the maximum call frame size of all the calls.
237218885Sdim  unsigned maxCallFrameSize = MFI->getMaxCallFrameSize();
238218885Sdim
239218885Sdim  // Maximum call frame needs to be at least big enough for linkage and 8 args.
240218885Sdim  unsigned minCallFrameSize = getMinCallFrameSize(Subtarget.isPPC64(),
241218885Sdim                                                  Subtarget.isDarwinABI());
242218885Sdim  maxCallFrameSize = std::max(maxCallFrameSize, minCallFrameSize);
243218885Sdim
244218885Sdim  // If we have dynamic alloca then maxCallFrameSize needs to be aligned so
245218885Sdim  // that allocations will be aligned.
246218885Sdim  if (MFI->hasVarSizedObjects())
247218885Sdim    maxCallFrameSize = (maxCallFrameSize + AlignMask) & ~AlignMask;
248218885Sdim
249218885Sdim  // Update maximum call frame size.
250249423Sdim  if (UpdateMF)
251249423Sdim    MFI->setMaxCallFrameSize(maxCallFrameSize);
252218885Sdim
253218885Sdim  // Include call frame size in total.
254218885Sdim  FrameSize += maxCallFrameSize;
255218885Sdim
256218885Sdim  // Make sure the frame is aligned.
257218885Sdim  FrameSize = (FrameSize + AlignMask) & ~AlignMask;
258218885Sdim
259218885Sdim  // Update frame info.
260249423Sdim  if (UpdateMF)
261249423Sdim    MFI->setStackSize(FrameSize);
262249423Sdim
263249423Sdim  return FrameSize;
264218885Sdim}
265218885Sdim
266218885Sdim// hasFP - Return true if the specified function actually has a dedicated frame
267218885Sdim// pointer register.
268218885Sdimbool PPCFrameLowering::hasFP(const MachineFunction &MF) const {
269218885Sdim  const MachineFrameInfo *MFI = MF.getFrameInfo();
270218885Sdim  // FIXME: This is pretty much broken by design: hasFP() might be called really
271218885Sdim  // early, before the stack layout was calculated and thus hasFP() might return
272218885Sdim  // true or false here depending on the time of call.
273218885Sdim  return (MFI->getStackSize()) && needsFP(MF);
274218885Sdim}
275218885Sdim
276218885Sdim// needsFP - Return true if the specified function should have a dedicated frame
277218885Sdim// pointer register.  This is true if the function has variable sized allocas or
278218885Sdim// if frame pointer elimination is disabled.
279218885Sdimbool PPCFrameLowering::needsFP(const MachineFunction &MF) const {
280218885Sdim  const MachineFrameInfo *MFI = MF.getFrameInfo();
281218885Sdim
282218885Sdim  // Naked functions have no stack frame pushed, so we don't have a frame
283218885Sdim  // pointer.
284249423Sdim  if (MF.getFunction()->getAttributes().hasAttribute(AttributeSet::FunctionIndex,
285249423Sdim                                                     Attribute::Naked))
286218885Sdim    return false;
287218885Sdim
288234353Sdim  return MF.getTarget().Options.DisableFramePointerElim(MF) ||
289234353Sdim    MFI->hasVarSizedObjects() ||
290234353Sdim    (MF.getTarget().Options.GuaranteedTailCallOpt &&
291234353Sdim     MF.getInfo<PPCFunctionInfo>()->hasFastCall());
292218885Sdim}
293218885Sdim
294249423Sdimvoid PPCFrameLowering::replaceFPWithRealFP(MachineFunction &MF) const {
295249423Sdim  bool is31 = needsFP(MF);
296249423Sdim  unsigned FPReg  = is31 ? PPC::R31 : PPC::R1;
297249423Sdim  unsigned FP8Reg = is31 ? PPC::X31 : PPC::X1;
298218885Sdim
299261991Sdim  const PPCRegisterInfo *RegInfo =
300261991Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
301261991Sdim  bool HasBP = RegInfo->hasBasePointer(MF);
302270147Srdivacky  unsigned BPReg  = HasBP ? (unsigned) RegInfo->getBaseRegister(MF): FPReg;
303261991Sdim  unsigned BP8Reg = HasBP ? (unsigned) PPC::X30 : FPReg;
304261991Sdim
305249423Sdim  for (MachineFunction::iterator BI = MF.begin(), BE = MF.end();
306249423Sdim       BI != BE; ++BI)
307249423Sdim    for (MachineBasicBlock::iterator MBBI = BI->end(); MBBI != BI->begin(); ) {
308249423Sdim      --MBBI;
309249423Sdim      for (unsigned I = 0, E = MBBI->getNumOperands(); I != E; ++I) {
310249423Sdim        MachineOperand &MO = MBBI->getOperand(I);
311249423Sdim        if (!MO.isReg())
312249423Sdim          continue;
313249423Sdim
314249423Sdim        switch (MO.getReg()) {
315249423Sdim        case PPC::FP:
316249423Sdim          MO.setReg(FPReg);
317249423Sdim          break;
318249423Sdim        case PPC::FP8:
319249423Sdim          MO.setReg(FP8Reg);
320249423Sdim          break;
321261991Sdim        case PPC::BP:
322261991Sdim          MO.setReg(BPReg);
323261991Sdim          break;
324261991Sdim        case PPC::BP8:
325261991Sdim          MO.setReg(BP8Reg);
326261991Sdim          break;
327261991Sdim
328249423Sdim        }
329249423Sdim      }
330249423Sdim    }
331249423Sdim}
332249423Sdim
333218885Sdimvoid PPCFrameLowering::emitPrologue(MachineFunction &MF) const {
334218885Sdim  MachineBasicBlock &MBB = MF.front();   // Prolog goes in entry BB
335218885Sdim  MachineBasicBlock::iterator MBBI = MBB.begin();
336218885Sdim  MachineFrameInfo *MFI = MF.getFrameInfo();
337218885Sdim  const PPCInstrInfo &TII =
338218885Sdim    *static_cast<const PPCInstrInfo*>(MF.getTarget().getInstrInfo());
339261991Sdim  const PPCRegisterInfo *RegInfo =
340261991Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
341218885Sdim
342218885Sdim  MachineModuleInfo &MMI = MF.getMMI();
343261991Sdim  const MCRegisterInfo *MRI = MMI.getContext().getRegisterInfo();
344218885Sdim  DebugLoc dl;
345218885Sdim  bool needsFrameMoves = MMI.hasDebugInfo() ||
346223017Sdim    MF.getFunction()->needsUnwindTableEntry();
347270147Srdivacky  bool isPIC = MF.getTarget().getRelocationModel() == Reloc::PIC_;
348218885Sdim
349261991Sdim  // Get processor type.
350261991Sdim  bool isPPC64 = Subtarget.isPPC64();
351261991Sdim  // Get the ABI.
352261991Sdim  bool isDarwinABI = Subtarget.isDarwinABI();
353261991Sdim  bool isSVR4ABI = Subtarget.isSVR4ABI();
354261991Sdim  assert((isDarwinABI || isSVR4ABI) &&
355261991Sdim         "Currently only Darwin and SVR4 ABIs are supported for PowerPC.");
356261991Sdim
357218885Sdim  // Prepare for frame info.
358218885Sdim  MCSymbol *FrameLabel = 0;
359218885Sdim
360218885Sdim  // Scan the prolog, looking for an UPDATE_VRSAVE instruction.  If we find it,
361218885Sdim  // process it.
362261991Sdim  if (!isSVR4ABI)
363243830Sdim    for (unsigned i = 0; MBBI != MBB.end(); ++i, ++MBBI) {
364243830Sdim      if (MBBI->getOpcode() == PPC::UPDATE_VRSAVE) {
365243830Sdim        HandleVRSaveUpdate(MBBI, TII);
366243830Sdim        break;
367243830Sdim      }
368218885Sdim    }
369218885Sdim
370218885Sdim  // Move MBBI back to the beginning of the function.
371218885Sdim  MBBI = MBB.begin();
372218885Sdim
373218885Sdim  // Work out frame sizes.
374249423Sdim  unsigned FrameSize = determineFrameLayout(MF);
375218885Sdim  int NegFrameSize = -FrameSize;
376261991Sdim  if (!isInt<32>(NegFrameSize))
377261991Sdim    llvm_unreachable("Unhandled stack size!");
378218885Sdim
379249423Sdim  if (MFI->isFrameAddressTaken())
380249423Sdim    replaceFPWithRealFP(MF);
381249423Sdim
382218885Sdim  // Check if the link register (LR) must be saved.
383218885Sdim  PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
384218885Sdim  bool MustSaveLR = FI->mustSaveLR();
385261991Sdim  const SmallVectorImpl<unsigned> &MustSaveCRs = FI->getMustSaveCRs();
386261991Sdim  // Do we have a frame pointer and/or base pointer for this function?
387218885Sdim  bool HasFP = hasFP(MF);
388261991Sdim  bool HasBP = RegInfo->hasBasePointer(MF);
389218885Sdim
390261991Sdim  unsigned SPReg       = isPPC64 ? PPC::X1  : PPC::R1;
391270147Srdivacky  unsigned BPReg       = RegInfo->getBaseRegister(MF);
392261991Sdim  unsigned FPReg       = isPPC64 ? PPC::X31 : PPC::R31;
393261991Sdim  unsigned LRReg       = isPPC64 ? PPC::LR8 : PPC::LR;
394261991Sdim  unsigned ScratchReg  = isPPC64 ? PPC::X0  : PPC::R0;
395261991Sdim  unsigned TempReg     = isPPC64 ? PPC::X12 : PPC::R12; // another scratch reg
396261991Sdim  //  ...(R12/X12 is volatile in both Darwin & SVR4, & can't be a function arg.)
397261991Sdim  const MCInstrDesc& MFLRInst = TII.get(isPPC64 ? PPC::MFLR8
398261991Sdim                                                : PPC::MFLR );
399261991Sdim  const MCInstrDesc& StoreInst = TII.get(isPPC64 ? PPC::STD
400261991Sdim                                                 : PPC::STW );
401261991Sdim  const MCInstrDesc& StoreUpdtInst = TII.get(isPPC64 ? PPC::STDU
402261991Sdim                                                     : PPC::STWU );
403261991Sdim  const MCInstrDesc& StoreUpdtIdxInst = TII.get(isPPC64 ? PPC::STDUX
404261991Sdim                                                        : PPC::STWUX);
405261991Sdim  const MCInstrDesc& LoadImmShiftedInst = TII.get(isPPC64 ? PPC::LIS8
406261991Sdim                                                          : PPC::LIS );
407261991Sdim  const MCInstrDesc& OrImmInst = TII.get(isPPC64 ? PPC::ORI8
408261991Sdim                                                 : PPC::ORI );
409261991Sdim  const MCInstrDesc& OrInst = TII.get(isPPC64 ? PPC::OR8
410261991Sdim                                              : PPC::OR );
411261991Sdim  const MCInstrDesc& SubtractCarryingInst = TII.get(isPPC64 ? PPC::SUBFC8
412261991Sdim                                                            : PPC::SUBFC);
413261991Sdim  const MCInstrDesc& SubtractImmCarryingInst = TII.get(isPPC64 ? PPC::SUBFIC8
414261991Sdim                                                               : PPC::SUBFIC);
415261991Sdim
416261991Sdim  // Regarding this assert: Even though LR is saved in the caller's frame (i.e.,
417261991Sdim  // LROffset is positive), that slot is callee-owned. Because PPC32 SVR4 has no
418261991Sdim  // Red Zone, an asynchronous event (a form of "callee") could claim a frame &
419261991Sdim  // overwrite it, so PPC32 SVR4 must claim at least a minimal frame to save LR.
420261991Sdim  assert((isPPC64 || !isSVR4ABI || !(!FrameSize && (MustSaveLR || HasFP))) &&
421261991Sdim         "FrameSize must be >0 to save/restore the FP or LR for 32-bit SVR4.");
422261991Sdim
423218885Sdim  int LROffset = PPCFrameLowering::getReturnSaveOffset(isPPC64, isDarwinABI);
424218885Sdim
425218885Sdim  int FPOffset = 0;
426218885Sdim  if (HasFP) {
427261991Sdim    if (isSVR4ABI) {
428218885Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
429218885Sdim      int FPIndex = FI->getFramePointerSaveIndex();
430218885Sdim      assert(FPIndex && "No Frame Pointer Save Slot!");
431218885Sdim      FPOffset = FFI->getObjectOffset(FPIndex);
432218885Sdim    } else {
433218885Sdim      FPOffset = PPCFrameLowering::getFramePointerSaveOffset(isPPC64, isDarwinABI);
434218885Sdim    }
435218885Sdim  }
436218885Sdim
437261991Sdim  int BPOffset = 0;
438261991Sdim  if (HasBP) {
439261991Sdim    if (isSVR4ABI) {
440261991Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
441261991Sdim      int BPIndex = FI->getBasePointerSaveIndex();
442261991Sdim      assert(BPIndex && "No Base Pointer Save Slot!");
443261991Sdim      BPOffset = FFI->getObjectOffset(BPIndex);
444261991Sdim    } else {
445261991Sdim      BPOffset =
446270147Srdivacky        PPCFrameLowering::getBasePointerSaveOffset(isPPC64,
447270147Srdivacky                                                   isDarwinABI,
448270147Srdivacky                                                   isPIC);
449251662Sdim    }
450261991Sdim  }
451251662Sdim
452261991Sdim  // Get stack alignments.
453261991Sdim  unsigned MaxAlign = MFI->getMaxAlignment();
454261991Sdim  if (HasBP && MaxAlign > 1)
455261991Sdim    assert(isPowerOf2_32(MaxAlign) && isInt<16>(MaxAlign) &&
456261991Sdim           "Invalid alignment!");
457218885Sdim
458261991Sdim  // Frames of 32KB & larger require special handling because they cannot be
459261991Sdim  // indexed into with a simple STDU/STWU/STD/STW immediate offset operand.
460261991Sdim  bool isLargeFrame = !isInt<16>(NegFrameSize);
461251662Sdim
462261991Sdim  if (MustSaveLR)
463261991Sdim    BuildMI(MBB, MBBI, dl, MFLRInst, ScratchReg);
464218885Sdim
465261991Sdim  assert((isPPC64 || MustSaveCRs.empty()) &&
466261991Sdim         "Prologue CR saving supported only in 64-bit mode");
467218885Sdim
468261991Sdim  if (!MustSaveCRs.empty()) { // will only occur for PPC64
469261991Sdim    MachineInstrBuilder MIB =
470261991Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::MFCR8), TempReg);
471261991Sdim    for (unsigned i = 0, e = MustSaveCRs.size(); i != e; ++i)
472261991Sdim      MIB.addReg(MustSaveCRs[i], RegState::ImplicitKill);
473218885Sdim  }
474218885Sdim
475261991Sdim  if (HasFP)
476261991Sdim    // FIXME: On PPC32 SVR4, we must not spill before claiming the stackframe.
477261991Sdim    BuildMI(MBB, MBBI, dl, StoreInst)
478261991Sdim      .addReg(FPReg)
479261991Sdim      .addImm(FPOffset)
480261991Sdim      .addReg(SPReg);
481261991Sdim
482261991Sdim  if (HasBP)
483261991Sdim    // FIXME: On PPC32 SVR4, we must not spill before claiming the stackframe.
484261991Sdim    BuildMI(MBB, MBBI, dl, StoreInst)
485261991Sdim      .addReg(BPReg)
486261991Sdim      .addImm(BPOffset)
487261991Sdim      .addReg(SPReg);
488261991Sdim
489261991Sdim  if (MustSaveLR)
490261991Sdim    // FIXME: On PPC32 SVR4, we must not spill before claiming the stackframe.
491261991Sdim    BuildMI(MBB, MBBI, dl, StoreInst)
492261991Sdim      .addReg(ScratchReg)
493261991Sdim      .addImm(LROffset)
494261991Sdim      .addReg(SPReg);
495261991Sdim
496261991Sdim  if (!MustSaveCRs.empty()) // will only occur for PPC64
497261991Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::STW8))
498261991Sdim      .addReg(TempReg, getKillRegState(true))
499261991Sdim      .addImm(8)
500261991Sdim      .addReg(SPReg);
501261991Sdim
502261991Sdim  // Skip the rest if this is a leaf function & all spills fit in the Red Zone.
503218885Sdim  if (!FrameSize) return;
504218885Sdim
505218885Sdim  // Adjust stack pointer: r1 += NegFrameSize.
506218885Sdim  // If there is a preferred stack alignment, align R1 now
507218885Sdim
508261991Sdim  if (HasBP) {
509261991Sdim    // Save a copy of r1 as the base pointer.
510261991Sdim    BuildMI(MBB, MBBI, dl, OrInst, BPReg)
511261991Sdim      .addReg(SPReg)
512261991Sdim      .addReg(SPReg);
513261991Sdim  }
514261991Sdim
515261991Sdim  if (HasBP && MaxAlign > 1) {
516261991Sdim    if (isPPC64)
517261991Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::RLDICL), ScratchReg)
518261991Sdim        .addReg(SPReg)
519218885Sdim        .addImm(0)
520261991Sdim        .addImm(64 - Log2_32(MaxAlign));
521261991Sdim    else // PPC32...
522261991Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::RLWINM), ScratchReg)
523261991Sdim        .addReg(SPReg)
524261991Sdim        .addImm(0)
525218885Sdim        .addImm(32 - Log2_32(MaxAlign))
526218885Sdim        .addImm(31);
527261991Sdim    if (!isLargeFrame) {
528261991Sdim      BuildMI(MBB, MBBI, dl, SubtractImmCarryingInst, ScratchReg)
529261991Sdim        .addReg(ScratchReg, RegState::Kill)
530218885Sdim        .addImm(NegFrameSize);
531218885Sdim    } else {
532261991Sdim      BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, TempReg)
533218885Sdim        .addImm(NegFrameSize >> 16);
534261991Sdim      BuildMI(MBB, MBBI, dl, OrImmInst, TempReg)
535261991Sdim        .addReg(TempReg, RegState::Kill)
536218885Sdim        .addImm(NegFrameSize & 0xFFFF);
537261991Sdim      BuildMI(MBB, MBBI, dl, SubtractCarryingInst, ScratchReg)
538261991Sdim        .addReg(ScratchReg, RegState::Kill)
539261991Sdim        .addReg(TempReg, RegState::Kill);
540218885Sdim    }
541261991Sdim    BuildMI(MBB, MBBI, dl, StoreUpdtIdxInst, SPReg)
542261991Sdim      .addReg(SPReg, RegState::Kill)
543261991Sdim      .addReg(SPReg)
544261991Sdim      .addReg(ScratchReg);
545218885Sdim
546261991Sdim  } else if (!isLargeFrame) {
547261991Sdim    BuildMI(MBB, MBBI, dl, StoreUpdtInst, SPReg)
548261991Sdim      .addReg(SPReg)
549261991Sdim      .addImm(NegFrameSize)
550261991Sdim      .addReg(SPReg);
551261991Sdim
552261991Sdim  } else {
553261991Sdim    BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, ScratchReg)
554261991Sdim      .addImm(NegFrameSize >> 16);
555261991Sdim    BuildMI(MBB, MBBI, dl, OrImmInst, ScratchReg)
556261991Sdim      .addReg(ScratchReg, RegState::Kill)
557261991Sdim      .addImm(NegFrameSize & 0xFFFF);
558261991Sdim    BuildMI(MBB, MBBI, dl, StoreUpdtIdxInst, SPReg)
559261991Sdim      .addReg(SPReg, RegState::Kill)
560261991Sdim      .addReg(SPReg)
561261991Sdim      .addReg(ScratchReg);
562218885Sdim  }
563218885Sdim
564218885Sdim  // Add the "machine moves" for the instructions we generated above, but in
565218885Sdim  // reverse order.
566218885Sdim  if (needsFrameMoves) {
567218885Sdim    // Mark effective beginning of when frame pointer becomes valid.
568218885Sdim    FrameLabel = MMI.getContext().CreateTempSymbol();
569218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::PROLOG_LABEL)).addSym(FrameLabel);
570218885Sdim
571218885Sdim    // Show update of SP.
572261991Sdim    assert(NegFrameSize);
573261991Sdim    MMI.addFrameInst(
574261991Sdim        MCCFIInstruction::createDefCfaOffset(FrameLabel, NegFrameSize));
575218885Sdim
576218885Sdim    if (HasFP) {
577261991Sdim      unsigned Reg = MRI->getDwarfRegNum(FPReg, true);
578261991Sdim      MMI.addFrameInst(
579261991Sdim          MCCFIInstruction::createOffset(FrameLabel, Reg, FPOffset));
580218885Sdim    }
581218885Sdim
582261991Sdim    if (HasBP) {
583261991Sdim      unsigned Reg = MRI->getDwarfRegNum(BPReg, true);
584261991Sdim      MMI.addFrameInst(
585261991Sdim          MCCFIInstruction::createOffset(FrameLabel, Reg, BPOffset));
586261991Sdim    }
587261991Sdim
588218885Sdim    if (MustSaveLR) {
589261991Sdim      unsigned Reg = MRI->getDwarfRegNum(LRReg, true);
590261991Sdim      MMI.addFrameInst(
591261991Sdim          MCCFIInstruction::createOffset(FrameLabel, Reg, LROffset));
592218885Sdim    }
593218885Sdim  }
594218885Sdim
595218885Sdim  MCSymbol *ReadyLabel = 0;
596218885Sdim
597218885Sdim  // If there is a frame pointer, copy R1 into R31
598218885Sdim  if (HasFP) {
599261991Sdim    BuildMI(MBB, MBBI, dl, OrInst, FPReg)
600261991Sdim      .addReg(SPReg)
601261991Sdim      .addReg(SPReg);
602218885Sdim
603218885Sdim    if (needsFrameMoves) {
604218885Sdim      ReadyLabel = MMI.getContext().CreateTempSymbol();
605218885Sdim
606218885Sdim      // Mark effective beginning of when frame pointer is ready.
607218885Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::PROLOG_LABEL)).addSym(ReadyLabel);
608218885Sdim
609261991Sdim      unsigned Reg = MRI->getDwarfRegNum(FPReg, true);
610261991Sdim      MMI.addFrameInst(MCCFIInstruction::createDefCfaRegister(ReadyLabel, Reg));
611218885Sdim    }
612218885Sdim  }
613218885Sdim
614218885Sdim  if (needsFrameMoves) {
615218885Sdim    MCSymbol *Label = HasFP ? ReadyLabel : FrameLabel;
616218885Sdim
617218885Sdim    // Add callee saved registers to move list.
618218885Sdim    const std::vector<CalleeSavedInfo> &CSI = MFI->getCalleeSavedInfo();
619218885Sdim    for (unsigned I = 0, E = CSI.size(); I != E; ++I) {
620218885Sdim      unsigned Reg = CSI[I].getReg();
621218885Sdim      if (Reg == PPC::LR || Reg == PPC::LR8 || Reg == PPC::RM) continue;
622223017Sdim
623223017Sdim      // This is a bit of a hack: CR2LT, CR2GT, CR2EQ and CR2UN are just
624223017Sdim      // subregisters of CR2. We just need to emit a move of CR2.
625239462Sdim      if (PPC::CRBITRCRegClass.contains(Reg))
626223017Sdim        continue;
627223017Sdim
628243830Sdim      // For SVR4, don't emit a move for the CR spill slot if we haven't
629243830Sdim      // spilled CRs.
630261991Sdim      if (isSVR4ABI && (PPC::CR2 <= Reg && Reg <= PPC::CR4)
631261991Sdim          && MustSaveCRs.empty())
632261991Sdim        continue;
633243830Sdim
634243830Sdim      // For 64-bit SVR4 when we have spilled CRs, the spill location
635243830Sdim      // is SP+8, not a frame-relative slot.
636261991Sdim      if (isSVR4ABI && isPPC64 && (PPC::CR2 <= Reg && Reg <= PPC::CR4)) {
637261991Sdim        MMI.addFrameInst(MCCFIInstruction::createOffset(
638261991Sdim            Label, MRI->getDwarfRegNum(PPC::CR2, true), 8));
639261991Sdim        continue;
640243830Sdim      }
641243830Sdim
642243830Sdim      int Offset = MFI->getObjectOffset(CSI[I].getFrameIdx());
643261991Sdim      MMI.addFrameInst(MCCFIInstruction::createOffset(
644261991Sdim          Label, MRI->getDwarfRegNum(Reg, true), Offset));
645218885Sdim    }
646218885Sdim  }
647218885Sdim}
648218885Sdim
649218885Sdimvoid PPCFrameLowering::emitEpilogue(MachineFunction &MF,
650218885Sdim                                MachineBasicBlock &MBB) const {
651218885Sdim  MachineBasicBlock::iterator MBBI = MBB.getLastNonDebugInstr();
652218885Sdim  assert(MBBI != MBB.end() && "Returning block has no terminator");
653218885Sdim  const PPCInstrInfo &TII =
654218885Sdim    *static_cast<const PPCInstrInfo*>(MF.getTarget().getInstrInfo());
655261991Sdim  const PPCRegisterInfo *RegInfo =
656261991Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
657218885Sdim
658218885Sdim  unsigned RetOpcode = MBBI->getOpcode();
659218885Sdim  DebugLoc dl;
660218885Sdim
661218885Sdim  assert((RetOpcode == PPC::BLR ||
662218885Sdim          RetOpcode == PPC::TCRETURNri ||
663218885Sdim          RetOpcode == PPC::TCRETURNdi ||
664218885Sdim          RetOpcode == PPC::TCRETURNai ||
665218885Sdim          RetOpcode == PPC::TCRETURNri8 ||
666218885Sdim          RetOpcode == PPC::TCRETURNdi8 ||
667218885Sdim          RetOpcode == PPC::TCRETURNai8) &&
668218885Sdim         "Can only insert epilog into returning blocks");
669218885Sdim
670261991Sdim  // Get alignment info so we know how to restore the SP.
671218885Sdim  const MachineFrameInfo *MFI = MF.getFrameInfo();
672218885Sdim
673218885Sdim  // Get the number of bytes allocated from the FrameInfo.
674218885Sdim  int FrameSize = MFI->getStackSize();
675218885Sdim
676218885Sdim  // Get processor type.
677218885Sdim  bool isPPC64 = Subtarget.isPPC64();
678261991Sdim  // Get the ABI.
679218885Sdim  bool isDarwinABI = Subtarget.isDarwinABI();
680261991Sdim  bool isSVR4ABI = Subtarget.isSVR4ABI();
681270147Srdivacky  bool isPIC = MF.getTarget().getRelocationModel() == Reloc::PIC_;
682261991Sdim
683218885Sdim  // Check if the link register (LR) has been saved.
684218885Sdim  PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
685218885Sdim  bool MustSaveLR = FI->mustSaveLR();
686261991Sdim  const SmallVectorImpl<unsigned> &MustSaveCRs = FI->getMustSaveCRs();
687261991Sdim  // Do we have a frame pointer and/or base pointer for this function?
688218885Sdim  bool HasFP = hasFP(MF);
689261991Sdim  bool HasBP = RegInfo->hasBasePointer(MF);
690218885Sdim
691261991Sdim  unsigned SPReg      = isPPC64 ? PPC::X1  : PPC::R1;
692270147Srdivacky  unsigned BPReg      = RegInfo->getBaseRegister(MF);
693261991Sdim  unsigned FPReg      = isPPC64 ? PPC::X31 : PPC::R31;
694261991Sdim  unsigned ScratchReg  = isPPC64 ? PPC::X0  : PPC::R0;
695261991Sdim  unsigned TempReg     = isPPC64 ? PPC::X12 : PPC::R12; // another scratch reg
696261991Sdim  const MCInstrDesc& MTLRInst = TII.get( isPPC64 ? PPC::MTLR8
697261991Sdim                                                 : PPC::MTLR );
698261991Sdim  const MCInstrDesc& LoadInst = TII.get( isPPC64 ? PPC::LD
699261991Sdim                                                 : PPC::LWZ );
700261991Sdim  const MCInstrDesc& LoadImmShiftedInst = TII.get( isPPC64 ? PPC::LIS8
701261991Sdim                                                           : PPC::LIS );
702261991Sdim  const MCInstrDesc& OrImmInst = TII.get( isPPC64 ? PPC::ORI8
703261991Sdim                                                  : PPC::ORI );
704261991Sdim  const MCInstrDesc& AddImmInst = TII.get( isPPC64 ? PPC::ADDI8
705261991Sdim                                                   : PPC::ADDI );
706261991Sdim  const MCInstrDesc& AddInst = TII.get( isPPC64 ? PPC::ADD8
707261991Sdim                                                : PPC::ADD4 );
708261991Sdim
709218885Sdim  int LROffset = PPCFrameLowering::getReturnSaveOffset(isPPC64, isDarwinABI);
710218885Sdim
711218885Sdim  int FPOffset = 0;
712218885Sdim  if (HasFP) {
713261991Sdim    if (isSVR4ABI) {
714218885Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
715218885Sdim      int FPIndex = FI->getFramePointerSaveIndex();
716218885Sdim      assert(FPIndex && "No Frame Pointer Save Slot!");
717218885Sdim      FPOffset = FFI->getObjectOffset(FPIndex);
718218885Sdim    } else {
719218885Sdim      FPOffset = PPCFrameLowering::getFramePointerSaveOffset(isPPC64, isDarwinABI);
720218885Sdim    }
721218885Sdim  }
722218885Sdim
723261991Sdim  int BPOffset = 0;
724261991Sdim  if (HasBP) {
725261991Sdim    if (isSVR4ABI) {
726261991Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
727261991Sdim      int BPIndex = FI->getBasePointerSaveIndex();
728261991Sdim      assert(BPIndex && "No Base Pointer Save Slot!");
729261991Sdim      BPOffset = FFI->getObjectOffset(BPIndex);
730261991Sdim    } else {
731261991Sdim      BPOffset =
732270147Srdivacky        PPCFrameLowering::getBasePointerSaveOffset(isPPC64,
733270147Srdivacky                                                   isDarwinABI,
734270147Srdivacky                                                   isPIC);
735261991Sdim    }
736261991Sdim  }
737261991Sdim
738218885Sdim  bool UsesTCRet =  RetOpcode == PPC::TCRETURNri ||
739218885Sdim    RetOpcode == PPC::TCRETURNdi ||
740218885Sdim    RetOpcode == PPC::TCRETURNai ||
741218885Sdim    RetOpcode == PPC::TCRETURNri8 ||
742218885Sdim    RetOpcode == PPC::TCRETURNdi8 ||
743218885Sdim    RetOpcode == PPC::TCRETURNai8;
744218885Sdim
745218885Sdim  if (UsesTCRet) {
746218885Sdim    int MaxTCRetDelta = FI->getTailCallSPDelta();
747218885Sdim    MachineOperand &StackAdjust = MBBI->getOperand(1);
748218885Sdim    assert(StackAdjust.isImm() && "Expecting immediate value.");
749218885Sdim    // Adjust stack pointer.
750218885Sdim    int StackAdj = StackAdjust.getImm();
751218885Sdim    int Delta = StackAdj - MaxTCRetDelta;
752218885Sdim    assert((Delta >= 0) && "Delta must be positive");
753218885Sdim    if (MaxTCRetDelta>0)
754218885Sdim      FrameSize += (StackAdj +Delta);
755218885Sdim    else
756218885Sdim      FrameSize += StackAdj;
757218885Sdim  }
758218885Sdim
759261991Sdim  // Frames of 32KB & larger require special handling because they cannot be
760261991Sdim  // indexed into with a simple LD/LWZ immediate offset operand.
761261991Sdim  bool isLargeFrame = !isInt<16>(FrameSize);
762261991Sdim
763218885Sdim  if (FrameSize) {
764261991Sdim    // In the prologue, the loaded (or persistent) stack pointer value is offset
765261991Sdim    // by the STDU/STDUX/STWU/STWUX instruction.  Add this offset back now.
766261991Sdim
767261991Sdim    // If this function contained a fastcc call and GuaranteedTailCallOpt is
768261991Sdim    // enabled (=> hasFastCall()==true) the fastcc call might contain a tail
769261991Sdim    // call which invalidates the stack pointer value in SP(0). So we use the
770261991Sdim    // value of R31 in this case.
771261991Sdim    if (FI->hasFastCall()) {
772261991Sdim      assert(HasFP && "Expecting a valid frame pointer.");
773261991Sdim      if (!isLargeFrame) {
774261991Sdim        BuildMI(MBB, MBBI, dl, AddImmInst, SPReg)
775261991Sdim          .addReg(FPReg).addImm(FrameSize);
776261991Sdim      } else {
777261991Sdim        BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, ScratchReg)
778218885Sdim          .addImm(FrameSize >> 16);
779261991Sdim        BuildMI(MBB, MBBI, dl, OrImmInst, ScratchReg)
780261991Sdim          .addReg(ScratchReg, RegState::Kill)
781218885Sdim          .addImm(FrameSize & 0xFFFF);
782261991Sdim        BuildMI(MBB, MBBI, dl, AddInst)
783261991Sdim          .addReg(SPReg)
784261991Sdim          .addReg(FPReg)
785261991Sdim          .addReg(ScratchReg);
786218885Sdim      }
787261991Sdim    } else if (!isLargeFrame && !HasBP && !MFI->hasVarSizedObjects()) {
788261991Sdim      BuildMI(MBB, MBBI, dl, AddImmInst, SPReg)
789261991Sdim        .addReg(SPReg)
790261991Sdim        .addImm(FrameSize);
791218885Sdim    } else {
792261991Sdim      BuildMI(MBB, MBBI, dl, LoadInst, SPReg)
793261991Sdim        .addImm(0)
794261991Sdim        .addReg(SPReg);
795218885Sdim    }
796261991Sdim
797218885Sdim  }
798218885Sdim
799261991Sdim  if (MustSaveLR)
800261991Sdim    BuildMI(MBB, MBBI, dl, LoadInst, ScratchReg)
801261991Sdim      .addImm(LROffset)
802261991Sdim      .addReg(SPReg);
803218885Sdim
804261991Sdim  assert((isPPC64 || MustSaveCRs.empty()) &&
805261991Sdim         "Epilogue CR restoring supported only in 64-bit mode");
806251662Sdim
807261991Sdim  if (!MustSaveCRs.empty()) // will only occur for PPC64
808261991Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::LWZ8), TempReg)
809261991Sdim      .addImm(8)
810261991Sdim      .addReg(SPReg);
811218885Sdim
812261991Sdim  if (HasFP)
813261991Sdim    BuildMI(MBB, MBBI, dl, LoadInst, FPReg)
814261991Sdim      .addImm(FPOffset)
815261991Sdim      .addReg(SPReg);
816251662Sdim
817261991Sdim  if (HasBP)
818261991Sdim    BuildMI(MBB, MBBI, dl, LoadInst, BPReg)
819261991Sdim      .addImm(BPOffset)
820261991Sdim      .addReg(SPReg);
821218885Sdim
822261991Sdim  if (!MustSaveCRs.empty()) // will only occur for PPC64
823261991Sdim    for (unsigned i = 0, e = MustSaveCRs.size(); i != e; ++i)
824261991Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::MTOCRF8), MustSaveCRs[i])
825261991Sdim        .addReg(TempReg, getKillRegState(i == e-1));
826251662Sdim
827261991Sdim  if (MustSaveLR)
828261991Sdim    BuildMI(MBB, MBBI, dl, MTLRInst).addReg(ScratchReg);
829218885Sdim
830218885Sdim  // Callee pop calling convention. Pop parameter/linkage area. Used for tail
831218885Sdim  // call optimization
832234353Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt && RetOpcode == PPC::BLR &&
833218885Sdim      MF.getFunction()->getCallingConv() == CallingConv::Fast) {
834218885Sdim     PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
835218885Sdim     unsigned CallerAllocatedAmt = FI->getMinReservedArea();
836218885Sdim
837218885Sdim     if (CallerAllocatedAmt && isInt<16>(CallerAllocatedAmt)) {
838261991Sdim       BuildMI(MBB, MBBI, dl, AddImmInst, SPReg)
839261991Sdim         .addReg(SPReg).addImm(CallerAllocatedAmt);
840218885Sdim     } else {
841261991Sdim       BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, ScratchReg)
842218885Sdim          .addImm(CallerAllocatedAmt >> 16);
843261991Sdim       BuildMI(MBB, MBBI, dl, OrImmInst, ScratchReg)
844261991Sdim          .addReg(ScratchReg, RegState::Kill)
845218885Sdim          .addImm(CallerAllocatedAmt & 0xFFFF);
846261991Sdim       BuildMI(MBB, MBBI, dl, AddInst)
847261991Sdim          .addReg(SPReg)
848218885Sdim          .addReg(FPReg)
849261991Sdim          .addReg(ScratchReg);
850218885Sdim     }
851218885Sdim  } else if (RetOpcode == PPC::TCRETURNdi) {
852218885Sdim    MBBI = MBB.getLastNonDebugInstr();
853218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
854218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILB)).
855218885Sdim      addGlobalAddress(JumpTarget.getGlobal(), JumpTarget.getOffset());
856218885Sdim  } else if (RetOpcode == PPC::TCRETURNri) {
857218885Sdim    MBBI = MBB.getLastNonDebugInstr();
858218885Sdim    assert(MBBI->getOperand(0).isReg() && "Expecting register operand.");
859218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBCTR));
860218885Sdim  } else if (RetOpcode == PPC::TCRETURNai) {
861218885Sdim    MBBI = MBB.getLastNonDebugInstr();
862218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
863218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBA)).addImm(JumpTarget.getImm());
864218885Sdim  } else if (RetOpcode == PPC::TCRETURNdi8) {
865218885Sdim    MBBI = MBB.getLastNonDebugInstr();
866218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
867218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILB8)).
868218885Sdim      addGlobalAddress(JumpTarget.getGlobal(), JumpTarget.getOffset());
869218885Sdim  } else if (RetOpcode == PPC::TCRETURNri8) {
870218885Sdim    MBBI = MBB.getLastNonDebugInstr();
871218885Sdim    assert(MBBI->getOperand(0).isReg() && "Expecting register operand.");
872218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBCTR8));
873218885Sdim  } else if (RetOpcode == PPC::TCRETURNai8) {
874218885Sdim    MBBI = MBB.getLastNonDebugInstr();
875218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
876218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBA8)).addImm(JumpTarget.getImm());
877218885Sdim  }
878218885Sdim}
879218885Sdim
880218885Sdim/// MustSaveLR - Return true if this function requires that we save the LR
881218885Sdim/// register onto the stack in the prolog and restore it in the epilog of the
882218885Sdim/// function.
883218885Sdimstatic bool MustSaveLR(const MachineFunction &MF, unsigned LR) {
884218885Sdim  const PPCFunctionInfo *MFI = MF.getInfo<PPCFunctionInfo>();
885218885Sdim
886218885Sdim  // We need a save/restore of LR if there is any def of LR (which is
887218885Sdim  // defined by calls, including the PIC setup sequence), or if there is
888218885Sdim  // some use of the LR stack slot (e.g. for builtin_return_address).
889218885Sdim  // (LR comes in 32 and 64 bit versions.)
890218885Sdim  MachineRegisterInfo::def_iterator RI = MF.getRegInfo().def_begin(LR);
891218885Sdim  return RI !=MF.getRegInfo().def_end() || MFI->isLRStoreRequired();
892218885Sdim}
893218885Sdim
894218885Sdimvoid
895218885SdimPPCFrameLowering::processFunctionBeforeCalleeSavedScan(MachineFunction &MF,
896249423Sdim                                                   RegScavenger *) const {
897261991Sdim  const PPCRegisterInfo *RegInfo =
898261991Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
899218885Sdim
900218885Sdim  //  Save and clear the LR state.
901218885Sdim  PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
902218885Sdim  unsigned LR = RegInfo->getRARegister();
903218885Sdim  FI->setMustSaveLR(MustSaveLR(MF, LR));
904249423Sdim  MachineRegisterInfo &MRI = MF.getRegInfo();
905249423Sdim  MRI.setPhysRegUnused(LR);
906218885Sdim
907218885Sdim  //  Save R31 if necessary
908218885Sdim  int FPSI = FI->getFramePointerSaveIndex();
909218885Sdim  bool isPPC64 = Subtarget.isPPC64();
910218885Sdim  bool isDarwinABI  = Subtarget.isDarwinABI();
911270147Srdivacky  bool isPIC = MF.getTarget().getRelocationModel() == Reloc::PIC_;
912218885Sdim  MachineFrameInfo *MFI = MF.getFrameInfo();
913218885Sdim
914218885Sdim  // If the frame pointer save index hasn't been defined yet.
915218885Sdim  if (!FPSI && needsFP(MF)) {
916218885Sdim    // Find out what the fix offset of the frame pointer save area.
917218885Sdim    int FPOffset = getFramePointerSaveOffset(isPPC64, isDarwinABI);
918218885Sdim    // Allocate the frame index for frame pointer save area.
919218885Sdim    FPSI = MFI->CreateFixedObject(isPPC64? 8 : 4, FPOffset, true);
920218885Sdim    // Save the result.
921218885Sdim    FI->setFramePointerSaveIndex(FPSI);
922218885Sdim  }
923218885Sdim
924261991Sdim  int BPSI = FI->getBasePointerSaveIndex();
925261991Sdim  if (!BPSI && RegInfo->hasBasePointer(MF)) {
926270147Srdivacky    int BPOffset = getBasePointerSaveOffset(isPPC64, isDarwinABI, isPIC);
927261991Sdim    // Allocate the frame index for the base pointer save area.
928261991Sdim    BPSI = MFI->CreateFixedObject(isPPC64? 8 : 4, BPOffset, true);
929261991Sdim    // Save the result.
930261991Sdim    FI->setBasePointerSaveIndex(BPSI);
931261991Sdim  }
932261991Sdim
933218885Sdim  // Reserve stack space to move the linkage area to in case of a tail call.
934218885Sdim  int TCSPDelta = 0;
935234353Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt &&
936234353Sdim      (TCSPDelta = FI->getTailCallSPDelta()) < 0) {
937218885Sdim    MFI->CreateFixedObject(-1 * TCSPDelta, TCSPDelta, true);
938218885Sdim  }
939218885Sdim
940249423Sdim  // For 32-bit SVR4, allocate the nonvolatile CR spill slot iff the
941249423Sdim  // function uses CR 2, 3, or 4.
942249423Sdim  if (!isPPC64 && !isDarwinABI &&
943249423Sdim      (MRI.isPhysRegUsed(PPC::CR2) ||
944249423Sdim       MRI.isPhysRegUsed(PPC::CR3) ||
945249423Sdim       MRI.isPhysRegUsed(PPC::CR4))) {
946249423Sdim    int FrameIdx = MFI->CreateFixedObject((uint64_t)4, (int64_t)-4, true);
947249423Sdim    FI->setCRSpillFrameIndex(FrameIdx);
948249423Sdim  }
949218885Sdim}
950218885Sdim
951249423Sdimvoid PPCFrameLowering::processFunctionBeforeFrameFinalized(MachineFunction &MF,
952249423Sdim                                                       RegScavenger *RS) const {
953218885Sdim  // Early exit if not using the SVR4 ABI.
954249423Sdim  if (!Subtarget.isSVR4ABI()) {
955249423Sdim    addScavengingSpillSlot(MF, RS);
956218885Sdim    return;
957249423Sdim  }
958218885Sdim
959218885Sdim  // Get callee saved register information.
960218885Sdim  MachineFrameInfo *FFI = MF.getFrameInfo();
961218885Sdim  const std::vector<CalleeSavedInfo> &CSI = FFI->getCalleeSavedInfo();
962218885Sdim
963218885Sdim  // Early exit if no callee saved registers are modified!
964218885Sdim  if (CSI.empty() && !needsFP(MF)) {
965249423Sdim    addScavengingSpillSlot(MF, RS);
966218885Sdim    return;
967218885Sdim  }
968218885Sdim
969218885Sdim  unsigned MinGPR = PPC::R31;
970218885Sdim  unsigned MinG8R = PPC::X31;
971218885Sdim  unsigned MinFPR = PPC::F31;
972218885Sdim  unsigned MinVR = PPC::V31;
973218885Sdim
974218885Sdim  bool HasGPSaveArea = false;
975218885Sdim  bool HasG8SaveArea = false;
976218885Sdim  bool HasFPSaveArea = false;
977218885Sdim  bool HasVRSAVESaveArea = false;
978218885Sdim  bool HasVRSaveArea = false;
979218885Sdim
980218885Sdim  SmallVector<CalleeSavedInfo, 18> GPRegs;
981218885Sdim  SmallVector<CalleeSavedInfo, 18> G8Regs;
982218885Sdim  SmallVector<CalleeSavedInfo, 18> FPRegs;
983218885Sdim  SmallVector<CalleeSavedInfo, 18> VRegs;
984218885Sdim
985218885Sdim  for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
986218885Sdim    unsigned Reg = CSI[i].getReg();
987239462Sdim    if (PPC::GPRCRegClass.contains(Reg)) {
988218885Sdim      HasGPSaveArea = true;
989218885Sdim
990218885Sdim      GPRegs.push_back(CSI[i]);
991218885Sdim
992218885Sdim      if (Reg < MinGPR) {
993218885Sdim        MinGPR = Reg;
994218885Sdim      }
995239462Sdim    } else if (PPC::G8RCRegClass.contains(Reg)) {
996218885Sdim      HasG8SaveArea = true;
997218885Sdim
998218885Sdim      G8Regs.push_back(CSI[i]);
999218885Sdim
1000218885Sdim      if (Reg < MinG8R) {
1001218885Sdim        MinG8R = Reg;
1002218885Sdim      }
1003239462Sdim    } else if (PPC::F8RCRegClass.contains(Reg)) {
1004218885Sdim      HasFPSaveArea = true;
1005218885Sdim
1006218885Sdim      FPRegs.push_back(CSI[i]);
1007218885Sdim
1008218885Sdim      if (Reg < MinFPR) {
1009218885Sdim        MinFPR = Reg;
1010218885Sdim      }
1011239462Sdim    } else if (PPC::CRBITRCRegClass.contains(Reg) ||
1012239462Sdim               PPC::CRRCRegClass.contains(Reg)) {
1013243830Sdim      ; // do nothing, as we already know whether CRs are spilled
1014239462Sdim    } else if (PPC::VRSAVERCRegClass.contains(Reg)) {
1015218885Sdim      HasVRSAVESaveArea = true;
1016239462Sdim    } else if (PPC::VRRCRegClass.contains(Reg)) {
1017218885Sdim      HasVRSaveArea = true;
1018218885Sdim
1019218885Sdim      VRegs.push_back(CSI[i]);
1020218885Sdim
1021218885Sdim      if (Reg < MinVR) {
1022218885Sdim        MinVR = Reg;
1023218885Sdim      }
1024218885Sdim    } else {
1025218885Sdim      llvm_unreachable("Unknown RegisterClass!");
1026218885Sdim    }
1027218885Sdim  }
1028218885Sdim
1029218885Sdim  PPCFunctionInfo *PFI = MF.getInfo<PPCFunctionInfo>();
1030249423Sdim  const TargetRegisterInfo *TRI = MF.getTarget().getRegisterInfo();
1031218885Sdim
1032218885Sdim  int64_t LowerBound = 0;
1033218885Sdim
1034218885Sdim  // Take into account stack space reserved for tail calls.
1035218885Sdim  int TCSPDelta = 0;
1036234353Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt &&
1037234353Sdim      (TCSPDelta = PFI->getTailCallSPDelta()) < 0) {
1038218885Sdim    LowerBound = TCSPDelta;
1039218885Sdim  }
1040218885Sdim
1041218885Sdim  // The Floating-point register save area is right below the back chain word
1042218885Sdim  // of the previous stack frame.
1043218885Sdim  if (HasFPSaveArea) {
1044218885Sdim    for (unsigned i = 0, e = FPRegs.size(); i != e; ++i) {
1045218885Sdim      int FI = FPRegs[i].getFrameIdx();
1046218885Sdim
1047218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1048218885Sdim    }
1049218885Sdim
1050249423Sdim    LowerBound -= (31 - TRI->getEncodingValue(MinFPR) + 1) * 8;
1051218885Sdim  }
1052218885Sdim
1053218885Sdim  // Check whether the frame pointer register is allocated. If so, make sure it
1054218885Sdim  // is spilled to the correct offset.
1055218885Sdim  if (needsFP(MF)) {
1056218885Sdim    HasGPSaveArea = true;
1057218885Sdim
1058218885Sdim    int FI = PFI->getFramePointerSaveIndex();
1059218885Sdim    assert(FI && "No Frame Pointer Save Slot!");
1060218885Sdim
1061218885Sdim    FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1062218885Sdim  }
1063218885Sdim
1064261991Sdim  const PPCRegisterInfo *RegInfo =
1065261991Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
1066261991Sdim  if (RegInfo->hasBasePointer(MF)) {
1067261991Sdim    HasGPSaveArea = true;
1068261991Sdim
1069261991Sdim    int FI = PFI->getBasePointerSaveIndex();
1070261991Sdim    assert(FI && "No Base Pointer Save Slot!");
1071261991Sdim
1072261991Sdim    FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1073261991Sdim  }
1074261991Sdim
1075218885Sdim  // General register save area starts right below the Floating-point
1076218885Sdim  // register save area.
1077218885Sdim  if (HasGPSaveArea || HasG8SaveArea) {
1078218885Sdim    // Move general register save area spill slots down, taking into account
1079218885Sdim    // the size of the Floating-point register save area.
1080218885Sdim    for (unsigned i = 0, e = GPRegs.size(); i != e; ++i) {
1081218885Sdim      int FI = GPRegs[i].getFrameIdx();
1082218885Sdim
1083218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1084218885Sdim    }
1085218885Sdim
1086218885Sdim    // Move general register save area spill slots down, taking into account
1087218885Sdim    // the size of the Floating-point register save area.
1088218885Sdim    for (unsigned i = 0, e = G8Regs.size(); i != e; ++i) {
1089218885Sdim      int FI = G8Regs[i].getFrameIdx();
1090218885Sdim
1091218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1092218885Sdim    }
1093218885Sdim
1094218885Sdim    unsigned MinReg =
1095249423Sdim      std::min<unsigned>(TRI->getEncodingValue(MinGPR),
1096249423Sdim                         TRI->getEncodingValue(MinG8R));
1097218885Sdim
1098218885Sdim    if (Subtarget.isPPC64()) {
1099218885Sdim      LowerBound -= (31 - MinReg + 1) * 8;
1100218885Sdim    } else {
1101218885Sdim      LowerBound -= (31 - MinReg + 1) * 4;
1102218885Sdim    }
1103218885Sdim  }
1104218885Sdim
1105243830Sdim  // For 32-bit only, the CR save area is below the general register
1106243830Sdim  // save area.  For 64-bit SVR4, the CR save area is addressed relative
1107243830Sdim  // to the stack pointer and hence does not need an adjustment here.
1108243830Sdim  // Only CR2 (the first nonvolatile spilled) has an associated frame
1109243830Sdim  // index so that we have a single uniform save area.
1110243830Sdim  if (spillsCR(MF) && !(Subtarget.isPPC64() && Subtarget.isSVR4ABI())) {
1111218885Sdim    // Adjust the frame index of the CR spill slot.
1112218885Sdim    for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1113218885Sdim      unsigned Reg = CSI[i].getReg();
1114218885Sdim
1115243830Sdim      if ((Subtarget.isSVR4ABI() && Reg == PPC::CR2)
1116243830Sdim	  // Leave Darwin logic as-is.
1117243830Sdim	  || (!Subtarget.isSVR4ABI() &&
1118243830Sdim	      (PPC::CRBITRCRegClass.contains(Reg) ||
1119243830Sdim	       PPC::CRRCRegClass.contains(Reg)))) {
1120218885Sdim        int FI = CSI[i].getFrameIdx();
1121218885Sdim
1122218885Sdim        FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1123218885Sdim      }
1124218885Sdim    }
1125218885Sdim
1126218885Sdim    LowerBound -= 4; // The CR save area is always 4 bytes long.
1127218885Sdim  }
1128218885Sdim
1129218885Sdim  if (HasVRSAVESaveArea) {
1130218885Sdim    // FIXME SVR4: Is it actually possible to have multiple elements in CSI
1131218885Sdim    //             which have the VRSAVE register class?
1132218885Sdim    // Adjust the frame index of the VRSAVE spill slot.
1133218885Sdim    for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1134218885Sdim      unsigned Reg = CSI[i].getReg();
1135218885Sdim
1136239462Sdim      if (PPC::VRSAVERCRegClass.contains(Reg)) {
1137218885Sdim        int FI = CSI[i].getFrameIdx();
1138218885Sdim
1139218885Sdim        FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1140218885Sdim      }
1141218885Sdim    }
1142218885Sdim
1143218885Sdim    LowerBound -= 4; // The VRSAVE save area is always 4 bytes long.
1144218885Sdim  }
1145218885Sdim
1146218885Sdim  if (HasVRSaveArea) {
1147218885Sdim    // Insert alignment padding, we need 16-byte alignment.
1148218885Sdim    LowerBound = (LowerBound - 15) & ~(15);
1149218885Sdim
1150218885Sdim    for (unsigned i = 0, e = VRegs.size(); i != e; ++i) {
1151218885Sdim      int FI = VRegs[i].getFrameIdx();
1152218885Sdim
1153218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1154218885Sdim    }
1155218885Sdim  }
1156249423Sdim
1157249423Sdim  addScavengingSpillSlot(MF, RS);
1158218885Sdim}
1159243830Sdim
1160249423Sdimvoid
1161249423SdimPPCFrameLowering::addScavengingSpillSlot(MachineFunction &MF,
1162249423Sdim                                         RegScavenger *RS) const {
1163249423Sdim  // Reserve a slot closest to SP or frame pointer if we have a dynalloc or
1164249423Sdim  // a large stack, which will require scavenging a register to materialize a
1165249423Sdim  // large offset.
1166249423Sdim
1167249423Sdim  // We need to have a scavenger spill slot for spills if the frame size is
1168249423Sdim  // large. In case there is no free register for large-offset addressing,
1169249423Sdim  // this slot is used for the necessary emergency spill. Also, we need the
1170249423Sdim  // slot for dynamic stack allocations.
1171249423Sdim
1172249423Sdim  // The scavenger might be invoked if the frame offset does not fit into
1173249423Sdim  // the 16-bit immediate. We don't know the complete frame size here
1174249423Sdim  // because we've not yet computed callee-saved register spills or the
1175249423Sdim  // needed alignment padding.
1176249423Sdim  unsigned StackSize = determineFrameLayout(MF, false, true);
1177249423Sdim  MachineFrameInfo *MFI = MF.getFrameInfo();
1178249423Sdim  if (MFI->hasVarSizedObjects() || spillsCR(MF) || spillsVRSAVE(MF) ||
1179249423Sdim      hasNonRISpills(MF) || (hasSpills(MF) && !isInt<16>(StackSize))) {
1180249423Sdim    const TargetRegisterClass *GPRC = &PPC::GPRCRegClass;
1181249423Sdim    const TargetRegisterClass *G8RC = &PPC::G8RCRegClass;
1182249423Sdim    const TargetRegisterClass *RC = Subtarget.isPPC64() ? G8RC : GPRC;
1183249423Sdim    RS->addScavengingFrameIndex(MFI->CreateStackObject(RC->getSize(),
1184249423Sdim                                                       RC->getAlignment(),
1185249423Sdim                                                       false));
1186249423Sdim
1187261991Sdim    // Might we have over-aligned allocas?
1188261991Sdim    bool HasAlVars = MFI->hasVarSizedObjects() &&
1189261991Sdim                     MFI->getMaxAlignment() > getStackAlignment();
1190261991Sdim
1191249423Sdim    // These kinds of spills might need two registers.
1192261991Sdim    if (spillsCR(MF) || spillsVRSAVE(MF) || HasAlVars)
1193249423Sdim      RS->addScavengingFrameIndex(MFI->CreateStackObject(RC->getSize(),
1194249423Sdim                                                         RC->getAlignment(),
1195249423Sdim                                                         false));
1196249423Sdim
1197249423Sdim  }
1198249423Sdim}
1199249423Sdim
1200243830Sdimbool
1201243830SdimPPCFrameLowering::spillCalleeSavedRegisters(MachineBasicBlock &MBB,
1202243830Sdim				     MachineBasicBlock::iterator MI,
1203243830Sdim				     const std::vector<CalleeSavedInfo> &CSI,
1204243830Sdim				     const TargetRegisterInfo *TRI) const {
1205243830Sdim
1206243830Sdim  // Currently, this function only handles SVR4 32- and 64-bit ABIs.
1207243830Sdim  // Return false otherwise to maintain pre-existing behavior.
1208243830Sdim  if (!Subtarget.isSVR4ABI())
1209243830Sdim    return false;
1210243830Sdim
1211243830Sdim  MachineFunction *MF = MBB.getParent();
1212243830Sdim  const PPCInstrInfo &TII =
1213243830Sdim    *static_cast<const PPCInstrInfo*>(MF->getTarget().getInstrInfo());
1214243830Sdim  DebugLoc DL;
1215243830Sdim  bool CRSpilled = false;
1216251662Sdim  MachineInstrBuilder CRMIB;
1217243830Sdim
1218243830Sdim  for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1219243830Sdim    unsigned Reg = CSI[i].getReg();
1220261991Sdim    // Only Darwin actually uses the VRSAVE register, but it can still appear
1221261991Sdim    // here if, for example, @llvm.eh.unwind.init() is used.  If we're not on
1222261991Sdim    // Darwin, ignore it.
1223261991Sdim    if (Reg == PPC::VRSAVE && !Subtarget.isDarwinABI())
1224261991Sdim      continue;
1225261991Sdim
1226243830Sdim    // CR2 through CR4 are the nonvolatile CR fields.
1227243830Sdim    bool IsCRField = PPC::CR2 <= Reg && Reg <= PPC::CR4;
1228243830Sdim
1229243830Sdim    // Add the callee-saved register as live-in; it's killed at the spill.
1230243830Sdim    MBB.addLiveIn(Reg);
1231243830Sdim
1232251662Sdim    if (CRSpilled && IsCRField) {
1233251662Sdim      CRMIB.addReg(Reg, RegState::ImplicitKill);
1234251662Sdim      continue;
1235251662Sdim    }
1236251662Sdim
1237243830Sdim    // Insert the spill to the stack frame.
1238243830Sdim    if (IsCRField) {
1239251662Sdim      PPCFunctionInfo *FuncInfo = MF->getInfo<PPCFunctionInfo>();
1240243830Sdim      if (Subtarget.isPPC64()) {
1241251662Sdim        // The actual spill will happen at the start of the prologue.
1242251662Sdim        FuncInfo->addMustSaveCR(Reg);
1243243830Sdim      } else {
1244251662Sdim        CRSpilled = true;
1245251662Sdim        FuncInfo->setSpillsCR();
1246251662Sdim
1247243830Sdim	// 32-bit:  FP-relative.  Note that we made sure CR2-CR4 all have
1248243830Sdim	// the same frame index in PPCRegisterInfo::hasReservedSpillSlot.
1249251662Sdim	CRMIB = BuildMI(*MF, DL, TII.get(PPC::MFCR), PPC::R12)
1250251662Sdim                  .addReg(Reg, RegState::ImplicitKill);
1251251662Sdim
1252251662Sdim	MBB.insert(MI, CRMIB);
1253243830Sdim	MBB.insert(MI, addFrameReference(BuildMI(*MF, DL, TII.get(PPC::STW))
1254243830Sdim					 .addReg(PPC::R12,
1255243830Sdim						 getKillRegState(true)),
1256243830Sdim					 CSI[i].getFrameIdx()));
1257243830Sdim      }
1258243830Sdim    } else {
1259243830Sdim      const TargetRegisterClass *RC = TRI->getMinimalPhysRegClass(Reg);
1260243830Sdim      TII.storeRegToStackSlot(MBB, MI, Reg, true,
1261243830Sdim			      CSI[i].getFrameIdx(), RC, TRI);
1262243830Sdim    }
1263243830Sdim  }
1264243830Sdim  return true;
1265243830Sdim}
1266243830Sdim
1267243830Sdimstatic void
1268251662SdimrestoreCRs(bool isPPC64, bool is31,
1269251662Sdim           bool CR2Spilled, bool CR3Spilled, bool CR4Spilled,
1270243830Sdim	   MachineBasicBlock &MBB, MachineBasicBlock::iterator MI,
1271243830Sdim	   const std::vector<CalleeSavedInfo> &CSI, unsigned CSIIndex) {
1272243830Sdim
1273243830Sdim  MachineFunction *MF = MBB.getParent();
1274243830Sdim  const PPCInstrInfo &TII =
1275243830Sdim    *static_cast<const PPCInstrInfo*>(MF->getTarget().getInstrInfo());
1276243830Sdim  DebugLoc DL;
1277243830Sdim  unsigned RestoreOp, MoveReg;
1278243830Sdim
1279251662Sdim  if (isPPC64)
1280251662Sdim    // This is handled during epilogue generation.
1281251662Sdim    return;
1282251662Sdim  else {
1283243830Sdim    // 32-bit:  FP-relative
1284243830Sdim    MBB.insert(MI, addFrameReference(BuildMI(*MF, DL, TII.get(PPC::LWZ),
1285243830Sdim					     PPC::R12),
1286243830Sdim				     CSI[CSIIndex].getFrameIdx()));
1287261991Sdim    RestoreOp = PPC::MTOCRF;
1288243830Sdim    MoveReg = PPC::R12;
1289243830Sdim  }
1290243830Sdim
1291243830Sdim  if (CR2Spilled)
1292243830Sdim    MBB.insert(MI, BuildMI(*MF, DL, TII.get(RestoreOp), PPC::CR2)
1293249423Sdim               .addReg(MoveReg, getKillRegState(!CR3Spilled && !CR4Spilled)));
1294243830Sdim
1295243830Sdim  if (CR3Spilled)
1296243830Sdim    MBB.insert(MI, BuildMI(*MF, DL, TII.get(RestoreOp), PPC::CR3)
1297249423Sdim               .addReg(MoveReg, getKillRegState(!CR4Spilled)));
1298243830Sdim
1299243830Sdim  if (CR4Spilled)
1300243830Sdim    MBB.insert(MI, BuildMI(*MF, DL, TII.get(RestoreOp), PPC::CR4)
1301249423Sdim               .addReg(MoveReg, getKillRegState(true)));
1302243830Sdim}
1303243830Sdim
1304249423Sdimvoid PPCFrameLowering::
1305249423SdimeliminateCallFramePseudoInstr(MachineFunction &MF, MachineBasicBlock &MBB,
1306249423Sdim                              MachineBasicBlock::iterator I) const {
1307249423Sdim  const PPCInstrInfo &TII =
1308249423Sdim    *static_cast<const PPCInstrInfo*>(MF.getTarget().getInstrInfo());
1309249423Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt &&
1310249423Sdim      I->getOpcode() == PPC::ADJCALLSTACKUP) {
1311249423Sdim    // Add (actually subtract) back the amount the callee popped on return.
1312249423Sdim    if (int CalleeAmt =  I->getOperand(1).getImm()) {
1313249423Sdim      bool is64Bit = Subtarget.isPPC64();
1314249423Sdim      CalleeAmt *= -1;
1315249423Sdim      unsigned StackReg = is64Bit ? PPC::X1 : PPC::R1;
1316249423Sdim      unsigned TmpReg = is64Bit ? PPC::X0 : PPC::R0;
1317249423Sdim      unsigned ADDIInstr = is64Bit ? PPC::ADDI8 : PPC::ADDI;
1318249423Sdim      unsigned ADDInstr = is64Bit ? PPC::ADD8 : PPC::ADD4;
1319249423Sdim      unsigned LISInstr = is64Bit ? PPC::LIS8 : PPC::LIS;
1320249423Sdim      unsigned ORIInstr = is64Bit ? PPC::ORI8 : PPC::ORI;
1321249423Sdim      MachineInstr *MI = I;
1322249423Sdim      DebugLoc dl = MI->getDebugLoc();
1323249423Sdim
1324249423Sdim      if (isInt<16>(CalleeAmt)) {
1325249423Sdim        BuildMI(MBB, I, dl, TII.get(ADDIInstr), StackReg)
1326249423Sdim          .addReg(StackReg, RegState::Kill)
1327249423Sdim          .addImm(CalleeAmt);
1328249423Sdim      } else {
1329249423Sdim        MachineBasicBlock::iterator MBBI = I;
1330249423Sdim        BuildMI(MBB, MBBI, dl, TII.get(LISInstr), TmpReg)
1331249423Sdim          .addImm(CalleeAmt >> 16);
1332249423Sdim        BuildMI(MBB, MBBI, dl, TII.get(ORIInstr), TmpReg)
1333249423Sdim          .addReg(TmpReg, RegState::Kill)
1334249423Sdim          .addImm(CalleeAmt & 0xFFFF);
1335249423Sdim        BuildMI(MBB, MBBI, dl, TII.get(ADDInstr), StackReg)
1336249423Sdim          .addReg(StackReg, RegState::Kill)
1337249423Sdim          .addReg(TmpReg);
1338249423Sdim      }
1339249423Sdim    }
1340249423Sdim  }
1341249423Sdim  // Simply discard ADJCALLSTACKDOWN, ADJCALLSTACKUP instructions.
1342249423Sdim  MBB.erase(I);
1343249423Sdim}
1344249423Sdim
1345243830Sdimbool
1346243830SdimPPCFrameLowering::restoreCalleeSavedRegisters(MachineBasicBlock &MBB,
1347243830Sdim					MachineBasicBlock::iterator MI,
1348243830Sdim				        const std::vector<CalleeSavedInfo> &CSI,
1349243830Sdim					const TargetRegisterInfo *TRI) const {
1350243830Sdim
1351243830Sdim  // Currently, this function only handles SVR4 32- and 64-bit ABIs.
1352243830Sdim  // Return false otherwise to maintain pre-existing behavior.
1353243830Sdim  if (!Subtarget.isSVR4ABI())
1354243830Sdim    return false;
1355243830Sdim
1356243830Sdim  MachineFunction *MF = MBB.getParent();
1357243830Sdim  const PPCInstrInfo &TII =
1358243830Sdim    *static_cast<const PPCInstrInfo*>(MF->getTarget().getInstrInfo());
1359243830Sdim  bool CR2Spilled = false;
1360243830Sdim  bool CR3Spilled = false;
1361243830Sdim  bool CR4Spilled = false;
1362243830Sdim  unsigned CSIIndex = 0;
1363243830Sdim
1364243830Sdim  // Initialize insertion-point logic; we will be restoring in reverse
1365243830Sdim  // order of spill.
1366243830Sdim  MachineBasicBlock::iterator I = MI, BeforeI = I;
1367243830Sdim  bool AtStart = I == MBB.begin();
1368243830Sdim
1369243830Sdim  if (!AtStart)
1370243830Sdim    --BeforeI;
1371243830Sdim
1372243830Sdim  for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1373243830Sdim    unsigned Reg = CSI[i].getReg();
1374243830Sdim
1375261991Sdim    // Only Darwin actually uses the VRSAVE register, but it can still appear
1376261991Sdim    // here if, for example, @llvm.eh.unwind.init() is used.  If we're not on
1377261991Sdim    // Darwin, ignore it.
1378261991Sdim    if (Reg == PPC::VRSAVE && !Subtarget.isDarwinABI())
1379261991Sdim      continue;
1380261991Sdim
1381243830Sdim    if (Reg == PPC::CR2) {
1382243830Sdim      CR2Spilled = true;
1383243830Sdim      // The spill slot is associated only with CR2, which is the
1384243830Sdim      // first nonvolatile spilled.  Save it here.
1385243830Sdim      CSIIndex = i;
1386243830Sdim      continue;
1387243830Sdim    } else if (Reg == PPC::CR3) {
1388243830Sdim      CR3Spilled = true;
1389243830Sdim      continue;
1390243830Sdim    } else if (Reg == PPC::CR4) {
1391243830Sdim      CR4Spilled = true;
1392243830Sdim      continue;
1393243830Sdim    } else {
1394243830Sdim      // When we first encounter a non-CR register after seeing at
1395243830Sdim      // least one CR register, restore all spilled CRs together.
1396243830Sdim      if ((CR2Spilled || CR3Spilled || CR4Spilled)
1397243830Sdim	  && !(PPC::CR2 <= Reg && Reg <= PPC::CR4)) {
1398251662Sdim        bool is31 = needsFP(*MF);
1399251662Sdim        restoreCRs(Subtarget.isPPC64(), is31,
1400251662Sdim                   CR2Spilled, CR3Spilled, CR4Spilled,
1401243830Sdim		   MBB, I, CSI, CSIIndex);
1402243830Sdim	CR2Spilled = CR3Spilled = CR4Spilled = false;
1403243830Sdim      }
1404243830Sdim
1405243830Sdim      // Default behavior for non-CR saves.
1406243830Sdim      const TargetRegisterClass *RC = TRI->getMinimalPhysRegClass(Reg);
1407243830Sdim      TII.loadRegFromStackSlot(MBB, I, Reg, CSI[i].getFrameIdx(),
1408243830Sdim			       RC, TRI);
1409243830Sdim      assert(I != MBB.begin() &&
1410243830Sdim	     "loadRegFromStackSlot didn't insert any code!");
1411243830Sdim      }
1412243830Sdim
1413243830Sdim    // Insert in reverse order.
1414243830Sdim    if (AtStart)
1415243830Sdim      I = MBB.begin();
1416243830Sdim    else {
1417243830Sdim      I = BeforeI;
1418243830Sdim      ++I;
1419243830Sdim    }
1420243830Sdim  }
1421243830Sdim
1422243830Sdim  // If we haven't yet spilled the CRs, do so now.
1423251662Sdim  if (CR2Spilled || CR3Spilled || CR4Spilled) {
1424251662Sdim    bool is31 = needsFP(*MF);
1425251662Sdim    restoreCRs(Subtarget.isPPC64(), is31, CR2Spilled, CR3Spilled, CR4Spilled,
1426243830Sdim	       MBB, I, CSI, CSIIndex);
1427251662Sdim  }
1428243830Sdim
1429243830Sdim  return true;
1430243830Sdim}
1431243830Sdim
1432