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
207263508Sdim  // Get stack alignments. The frame must be aligned to the greatest of these:
208263508Sdim  unsigned TargetAlign = getStackAlignment(); // alignment required per the ABI
209263508Sdim  unsigned MaxAlign = MFI->getMaxAlignment(); // algmt required by data in frame
210263508Sdim  unsigned AlignMask = std::max(MaxAlign, TargetAlign) - 1;
211218885Sdim
212263508Sdim  const PPCRegisterInfo *RegInfo =
213263508Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
214263508Sdim
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.
229263508Sdim      !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
299263508Sdim  const PPCRegisterInfo *RegInfo =
300263508Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
301263508Sdim  bool HasBP = RegInfo->hasBasePointer(MF);
302263508Sdim  unsigned BPReg  = HasBP ? (unsigned) PPC::R30 : FPReg;
303263508Sdim  unsigned BP8Reg = HasBP ? (unsigned) PPC::X30 : FPReg;
304263508Sdim
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;
321263508Sdim        case PPC::BP:
322263508Sdim          MO.setReg(BPReg);
323263508Sdim          break;
324263508Sdim        case PPC::BP8:
325263508Sdim          MO.setReg(BP8Reg);
326263508Sdim          break;
327263508Sdim
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());
339263508Sdim  const PPCRegisterInfo *RegInfo =
340263508Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
341218885Sdim
342218885Sdim  MachineModuleInfo &MMI = MF.getMMI();
343263508Sdim  const MCRegisterInfo *MRI = MMI.getContext().getRegisterInfo();
344218885Sdim  DebugLoc dl;
345218885Sdim  bool needsFrameMoves = MMI.hasDebugInfo() ||
346223017Sdim    MF.getFunction()->needsUnwindTableEntry();
347218885Sdim
348263508Sdim  // Get processor type.
349263508Sdim  bool isPPC64 = Subtarget.isPPC64();
350263508Sdim  // Get the ABI.
351263508Sdim  bool isDarwinABI = Subtarget.isDarwinABI();
352263508Sdim  bool isSVR4ABI = Subtarget.isSVR4ABI();
353263508Sdim  assert((isDarwinABI || isSVR4ABI) &&
354263508Sdim         "Currently only Darwin and SVR4 ABIs are supported for PowerPC.");
355263508Sdim
356218885Sdim  // Prepare for frame info.
357218885Sdim  MCSymbol *FrameLabel = 0;
358218885Sdim
359218885Sdim  // Scan the prolog, looking for an UPDATE_VRSAVE instruction.  If we find it,
360218885Sdim  // process it.
361263508Sdim  if (!isSVR4ABI)
362243830Sdim    for (unsigned i = 0; MBBI != MBB.end(); ++i, ++MBBI) {
363243830Sdim      if (MBBI->getOpcode() == PPC::UPDATE_VRSAVE) {
364243830Sdim        HandleVRSaveUpdate(MBBI, TII);
365243830Sdim        break;
366243830Sdim      }
367218885Sdim    }
368218885Sdim
369218885Sdim  // Move MBBI back to the beginning of the function.
370218885Sdim  MBBI = MBB.begin();
371218885Sdim
372218885Sdim  // Work out frame sizes.
373249423Sdim  unsigned FrameSize = determineFrameLayout(MF);
374218885Sdim  int NegFrameSize = -FrameSize;
375263508Sdim  if (!isInt<32>(NegFrameSize))
376263508Sdim    llvm_unreachable("Unhandled stack size!");
377218885Sdim
378249423Sdim  if (MFI->isFrameAddressTaken())
379249423Sdim    replaceFPWithRealFP(MF);
380249423Sdim
381218885Sdim  // Check if the link register (LR) must be saved.
382218885Sdim  PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
383218885Sdim  bool MustSaveLR = FI->mustSaveLR();
384263508Sdim  const SmallVectorImpl<unsigned> &MustSaveCRs = FI->getMustSaveCRs();
385263508Sdim  // Do we have a frame pointer and/or base pointer for this function?
386218885Sdim  bool HasFP = hasFP(MF);
387263508Sdim  bool HasBP = RegInfo->hasBasePointer(MF);
388218885Sdim
389263508Sdim  unsigned SPReg       = isPPC64 ? PPC::X1  : PPC::R1;
390263508Sdim  unsigned BPReg       = isPPC64 ? PPC::X30 : PPC::R30;
391263508Sdim  unsigned FPReg       = isPPC64 ? PPC::X31 : PPC::R31;
392263508Sdim  unsigned LRReg       = isPPC64 ? PPC::LR8 : PPC::LR;
393263508Sdim  unsigned ScratchReg  = isPPC64 ? PPC::X0  : PPC::R0;
394263508Sdim  unsigned TempReg     = isPPC64 ? PPC::X12 : PPC::R12; // another scratch reg
395263508Sdim  //  ...(R12/X12 is volatile in both Darwin & SVR4, & can't be a function arg.)
396263508Sdim  const MCInstrDesc& MFLRInst = TII.get(isPPC64 ? PPC::MFLR8
397263508Sdim                                                : PPC::MFLR );
398263508Sdim  const MCInstrDesc& StoreInst = TII.get(isPPC64 ? PPC::STD
399263508Sdim                                                 : PPC::STW );
400263508Sdim  const MCInstrDesc& StoreUpdtInst = TII.get(isPPC64 ? PPC::STDU
401263508Sdim                                                     : PPC::STWU );
402263508Sdim  const MCInstrDesc& StoreUpdtIdxInst = TII.get(isPPC64 ? PPC::STDUX
403263508Sdim                                                        : PPC::STWUX);
404263508Sdim  const MCInstrDesc& LoadImmShiftedInst = TII.get(isPPC64 ? PPC::LIS8
405263508Sdim                                                          : PPC::LIS );
406263508Sdim  const MCInstrDesc& OrImmInst = TII.get(isPPC64 ? PPC::ORI8
407263508Sdim                                                 : PPC::ORI );
408263508Sdim  const MCInstrDesc& OrInst = TII.get(isPPC64 ? PPC::OR8
409263508Sdim                                              : PPC::OR );
410263508Sdim  const MCInstrDesc& SubtractCarryingInst = TII.get(isPPC64 ? PPC::SUBFC8
411263508Sdim                                                            : PPC::SUBFC);
412263508Sdim  const MCInstrDesc& SubtractImmCarryingInst = TII.get(isPPC64 ? PPC::SUBFIC8
413263508Sdim                                                               : PPC::SUBFIC);
414263508Sdim
415263508Sdim  // Regarding this assert: Even though LR is saved in the caller's frame (i.e.,
416263508Sdim  // LROffset is positive), that slot is callee-owned. Because PPC32 SVR4 has no
417263508Sdim  // Red Zone, an asynchronous event (a form of "callee") could claim a frame &
418263508Sdim  // overwrite it, so PPC32 SVR4 must claim at least a minimal frame to save LR.
419263508Sdim  assert((isPPC64 || !isSVR4ABI || !(!FrameSize && (MustSaveLR || HasFP))) &&
420263508Sdim         "FrameSize must be >0 to save/restore the FP or LR for 32-bit SVR4.");
421263508Sdim
422218885Sdim  int LROffset = PPCFrameLowering::getReturnSaveOffset(isPPC64, isDarwinABI);
423218885Sdim
424218885Sdim  int FPOffset = 0;
425218885Sdim  if (HasFP) {
426263508Sdim    if (isSVR4ABI) {
427218885Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
428218885Sdim      int FPIndex = FI->getFramePointerSaveIndex();
429218885Sdim      assert(FPIndex && "No Frame Pointer Save Slot!");
430218885Sdim      FPOffset = FFI->getObjectOffset(FPIndex);
431218885Sdim    } else {
432218885Sdim      FPOffset = PPCFrameLowering::getFramePointerSaveOffset(isPPC64, isDarwinABI);
433218885Sdim    }
434218885Sdim  }
435218885Sdim
436263508Sdim  int BPOffset = 0;
437263508Sdim  if (HasBP) {
438263508Sdim    if (isSVR4ABI) {
439263508Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
440263508Sdim      int BPIndex = FI->getBasePointerSaveIndex();
441263508Sdim      assert(BPIndex && "No Base Pointer Save Slot!");
442263508Sdim      BPOffset = FFI->getObjectOffset(BPIndex);
443263508Sdim    } else {
444263508Sdim      BPOffset =
445263508Sdim        PPCFrameLowering::getBasePointerSaveOffset(isPPC64, isDarwinABI);
446251662Sdim    }
447263508Sdim  }
448251662Sdim
449263508Sdim  // Get stack alignments.
450263508Sdim  unsigned MaxAlign = MFI->getMaxAlignment();
451263508Sdim  if (HasBP && MaxAlign > 1)
452263508Sdim    assert(isPowerOf2_32(MaxAlign) && isInt<16>(MaxAlign) &&
453263508Sdim           "Invalid alignment!");
454218885Sdim
455263508Sdim  // Frames of 32KB & larger require special handling because they cannot be
456263508Sdim  // indexed into with a simple STDU/STWU/STD/STW immediate offset operand.
457263508Sdim  bool isLargeFrame = !isInt<16>(NegFrameSize);
458251662Sdim
459263508Sdim  if (MustSaveLR)
460263508Sdim    BuildMI(MBB, MBBI, dl, MFLRInst, ScratchReg);
461218885Sdim
462263508Sdim  assert((isPPC64 || MustSaveCRs.empty()) &&
463263508Sdim         "Prologue CR saving supported only in 64-bit mode");
464218885Sdim
465263508Sdim  if (!MustSaveCRs.empty()) { // will only occur for PPC64
466263508Sdim    MachineInstrBuilder MIB =
467263508Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::MFCR8), TempReg);
468263508Sdim    for (unsigned i = 0, e = MustSaveCRs.size(); i != e; ++i)
469263508Sdim      MIB.addReg(MustSaveCRs[i], RegState::ImplicitKill);
470218885Sdim  }
471218885Sdim
472263508Sdim  if (HasFP)
473263508Sdim    // FIXME: On PPC32 SVR4, we must not spill before claiming the stackframe.
474263508Sdim    BuildMI(MBB, MBBI, dl, StoreInst)
475263508Sdim      .addReg(FPReg)
476263508Sdim      .addImm(FPOffset)
477263508Sdim      .addReg(SPReg);
478263508Sdim
479263508Sdim  if (HasBP)
480263508Sdim    // FIXME: On PPC32 SVR4, we must not spill before claiming the stackframe.
481263508Sdim    BuildMI(MBB, MBBI, dl, StoreInst)
482263508Sdim      .addReg(BPReg)
483263508Sdim      .addImm(BPOffset)
484263508Sdim      .addReg(SPReg);
485263508Sdim
486263508Sdim  if (MustSaveLR)
487263508Sdim    // FIXME: On PPC32 SVR4, we must not spill before claiming the stackframe.
488263508Sdim    BuildMI(MBB, MBBI, dl, StoreInst)
489263508Sdim      .addReg(ScratchReg)
490263508Sdim      .addImm(LROffset)
491263508Sdim      .addReg(SPReg);
492263508Sdim
493263508Sdim  if (!MustSaveCRs.empty()) // will only occur for PPC64
494263508Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::STW8))
495263508Sdim      .addReg(TempReg, getKillRegState(true))
496263508Sdim      .addImm(8)
497263508Sdim      .addReg(SPReg);
498263508Sdim
499263508Sdim  // Skip the rest if this is a leaf function & all spills fit in the Red Zone.
500218885Sdim  if (!FrameSize) return;
501218885Sdim
502218885Sdim  // Adjust stack pointer: r1 += NegFrameSize.
503218885Sdim  // If there is a preferred stack alignment, align R1 now
504218885Sdim
505263508Sdim  if (HasBP) {
506263508Sdim    // Save a copy of r1 as the base pointer.
507263508Sdim    BuildMI(MBB, MBBI, dl, OrInst, BPReg)
508263508Sdim      .addReg(SPReg)
509263508Sdim      .addReg(SPReg);
510263508Sdim  }
511263508Sdim
512263508Sdim  if (HasBP && MaxAlign > 1) {
513263508Sdim    if (isPPC64)
514263508Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::RLDICL), ScratchReg)
515263508Sdim        .addReg(SPReg)
516218885Sdim        .addImm(0)
517263508Sdim        .addImm(64 - Log2_32(MaxAlign));
518263508Sdim    else // PPC32...
519263508Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::RLWINM), ScratchReg)
520263508Sdim        .addReg(SPReg)
521263508Sdim        .addImm(0)
522218885Sdim        .addImm(32 - Log2_32(MaxAlign))
523218885Sdim        .addImm(31);
524263508Sdim    if (!isLargeFrame) {
525263508Sdim      BuildMI(MBB, MBBI, dl, SubtractImmCarryingInst, ScratchReg)
526263508Sdim        .addReg(ScratchReg, RegState::Kill)
527218885Sdim        .addImm(NegFrameSize);
528218885Sdim    } else {
529263508Sdim      BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, TempReg)
530218885Sdim        .addImm(NegFrameSize >> 16);
531263508Sdim      BuildMI(MBB, MBBI, dl, OrImmInst, TempReg)
532263508Sdim        .addReg(TempReg, RegState::Kill)
533218885Sdim        .addImm(NegFrameSize & 0xFFFF);
534263508Sdim      BuildMI(MBB, MBBI, dl, SubtractCarryingInst, ScratchReg)
535263508Sdim        .addReg(ScratchReg, RegState::Kill)
536263508Sdim        .addReg(TempReg, RegState::Kill);
537218885Sdim    }
538263508Sdim    BuildMI(MBB, MBBI, dl, StoreUpdtIdxInst, SPReg)
539263508Sdim      .addReg(SPReg, RegState::Kill)
540263508Sdim      .addReg(SPReg)
541263508Sdim      .addReg(ScratchReg);
542218885Sdim
543263508Sdim  } else if (!isLargeFrame) {
544263508Sdim    BuildMI(MBB, MBBI, dl, StoreUpdtInst, SPReg)
545263508Sdim      .addReg(SPReg)
546263508Sdim      .addImm(NegFrameSize)
547263508Sdim      .addReg(SPReg);
548263508Sdim
549263508Sdim  } else {
550263508Sdim    BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, ScratchReg)
551263508Sdim      .addImm(NegFrameSize >> 16);
552263508Sdim    BuildMI(MBB, MBBI, dl, OrImmInst, ScratchReg)
553263508Sdim      .addReg(ScratchReg, RegState::Kill)
554263508Sdim      .addImm(NegFrameSize & 0xFFFF);
555263508Sdim    BuildMI(MBB, MBBI, dl, StoreUpdtIdxInst, SPReg)
556263508Sdim      .addReg(SPReg, RegState::Kill)
557263508Sdim      .addReg(SPReg)
558263508Sdim      .addReg(ScratchReg);
559218885Sdim  }
560218885Sdim
561218885Sdim  // Add the "machine moves" for the instructions we generated above, but in
562218885Sdim  // reverse order.
563218885Sdim  if (needsFrameMoves) {
564218885Sdim    // Mark effective beginning of when frame pointer becomes valid.
565218885Sdim    FrameLabel = MMI.getContext().CreateTempSymbol();
566218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::PROLOG_LABEL)).addSym(FrameLabel);
567218885Sdim
568218885Sdim    // Show update of SP.
569263508Sdim    assert(NegFrameSize);
570263508Sdim    MMI.addFrameInst(
571263508Sdim        MCCFIInstruction::createDefCfaOffset(FrameLabel, NegFrameSize));
572218885Sdim
573218885Sdim    if (HasFP) {
574263508Sdim      unsigned Reg = MRI->getDwarfRegNum(FPReg, true);
575263508Sdim      MMI.addFrameInst(
576263508Sdim          MCCFIInstruction::createOffset(FrameLabel, Reg, FPOffset));
577218885Sdim    }
578218885Sdim
579263508Sdim    if (HasBP) {
580263508Sdim      unsigned Reg = MRI->getDwarfRegNum(BPReg, true);
581263508Sdim      MMI.addFrameInst(
582263508Sdim          MCCFIInstruction::createOffset(FrameLabel, Reg, BPOffset));
583263508Sdim    }
584263508Sdim
585218885Sdim    if (MustSaveLR) {
586263508Sdim      unsigned Reg = MRI->getDwarfRegNum(LRReg, true);
587263508Sdim      MMI.addFrameInst(
588263508Sdim          MCCFIInstruction::createOffset(FrameLabel, Reg, LROffset));
589218885Sdim    }
590218885Sdim  }
591218885Sdim
592218885Sdim  MCSymbol *ReadyLabel = 0;
593218885Sdim
594218885Sdim  // If there is a frame pointer, copy R1 into R31
595218885Sdim  if (HasFP) {
596263508Sdim    BuildMI(MBB, MBBI, dl, OrInst, FPReg)
597263508Sdim      .addReg(SPReg)
598263508Sdim      .addReg(SPReg);
599218885Sdim
600218885Sdim    if (needsFrameMoves) {
601218885Sdim      ReadyLabel = MMI.getContext().CreateTempSymbol();
602218885Sdim
603218885Sdim      // Mark effective beginning of when frame pointer is ready.
604218885Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::PROLOG_LABEL)).addSym(ReadyLabel);
605218885Sdim
606263508Sdim      unsigned Reg = MRI->getDwarfRegNum(FPReg, true);
607263508Sdim      MMI.addFrameInst(MCCFIInstruction::createDefCfaRegister(ReadyLabel, Reg));
608218885Sdim    }
609218885Sdim  }
610218885Sdim
611218885Sdim  if (needsFrameMoves) {
612218885Sdim    MCSymbol *Label = HasFP ? ReadyLabel : FrameLabel;
613218885Sdim
614218885Sdim    // Add callee saved registers to move list.
615218885Sdim    const std::vector<CalleeSavedInfo> &CSI = MFI->getCalleeSavedInfo();
616218885Sdim    for (unsigned I = 0, E = CSI.size(); I != E; ++I) {
617218885Sdim      unsigned Reg = CSI[I].getReg();
618218885Sdim      if (Reg == PPC::LR || Reg == PPC::LR8 || Reg == PPC::RM) continue;
619223017Sdim
620223017Sdim      // This is a bit of a hack: CR2LT, CR2GT, CR2EQ and CR2UN are just
621223017Sdim      // subregisters of CR2. We just need to emit a move of CR2.
622239462Sdim      if (PPC::CRBITRCRegClass.contains(Reg))
623223017Sdim        continue;
624223017Sdim
625243830Sdim      // For SVR4, don't emit a move for the CR spill slot if we haven't
626243830Sdim      // spilled CRs.
627263508Sdim      if (isSVR4ABI && (PPC::CR2 <= Reg && Reg <= PPC::CR4)
628263508Sdim          && MustSaveCRs.empty())
629263508Sdim        continue;
630243830Sdim
631243830Sdim      // For 64-bit SVR4 when we have spilled CRs, the spill location
632243830Sdim      // is SP+8, not a frame-relative slot.
633263508Sdim      if (isSVR4ABI && isPPC64 && (PPC::CR2 <= Reg && Reg <= PPC::CR4)) {
634263508Sdim        MMI.addFrameInst(MCCFIInstruction::createOffset(
635263508Sdim            Label, MRI->getDwarfRegNum(PPC::CR2, true), 8));
636263508Sdim        continue;
637243830Sdim      }
638243830Sdim
639243830Sdim      int Offset = MFI->getObjectOffset(CSI[I].getFrameIdx());
640263508Sdim      MMI.addFrameInst(MCCFIInstruction::createOffset(
641263508Sdim          Label, MRI->getDwarfRegNum(Reg, true), Offset));
642218885Sdim    }
643218885Sdim  }
644218885Sdim}
645218885Sdim
646218885Sdimvoid PPCFrameLowering::emitEpilogue(MachineFunction &MF,
647218885Sdim                                MachineBasicBlock &MBB) const {
648218885Sdim  MachineBasicBlock::iterator MBBI = MBB.getLastNonDebugInstr();
649218885Sdim  assert(MBBI != MBB.end() && "Returning block has no terminator");
650218885Sdim  const PPCInstrInfo &TII =
651218885Sdim    *static_cast<const PPCInstrInfo*>(MF.getTarget().getInstrInfo());
652263508Sdim  const PPCRegisterInfo *RegInfo =
653263508Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
654218885Sdim
655218885Sdim  unsigned RetOpcode = MBBI->getOpcode();
656218885Sdim  DebugLoc dl;
657218885Sdim
658218885Sdim  assert((RetOpcode == PPC::BLR ||
659218885Sdim          RetOpcode == PPC::TCRETURNri ||
660218885Sdim          RetOpcode == PPC::TCRETURNdi ||
661218885Sdim          RetOpcode == PPC::TCRETURNai ||
662218885Sdim          RetOpcode == PPC::TCRETURNri8 ||
663218885Sdim          RetOpcode == PPC::TCRETURNdi8 ||
664218885Sdim          RetOpcode == PPC::TCRETURNai8) &&
665218885Sdim         "Can only insert epilog into returning blocks");
666218885Sdim
667263508Sdim  // Get alignment info so we know how to restore the SP.
668218885Sdim  const MachineFrameInfo *MFI = MF.getFrameInfo();
669218885Sdim
670218885Sdim  // Get the number of bytes allocated from the FrameInfo.
671218885Sdim  int FrameSize = MFI->getStackSize();
672218885Sdim
673218885Sdim  // Get processor type.
674218885Sdim  bool isPPC64 = Subtarget.isPPC64();
675263508Sdim  // Get the ABI.
676218885Sdim  bool isDarwinABI = Subtarget.isDarwinABI();
677263508Sdim  bool isSVR4ABI = Subtarget.isSVR4ABI();
678263508Sdim
679218885Sdim  // Check if the link register (LR) has been saved.
680218885Sdim  PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
681218885Sdim  bool MustSaveLR = FI->mustSaveLR();
682263508Sdim  const SmallVectorImpl<unsigned> &MustSaveCRs = FI->getMustSaveCRs();
683263508Sdim  // Do we have a frame pointer and/or base pointer for this function?
684218885Sdim  bool HasFP = hasFP(MF);
685263508Sdim  bool HasBP = RegInfo->hasBasePointer(MF);
686218885Sdim
687263508Sdim  unsigned SPReg      = isPPC64 ? PPC::X1  : PPC::R1;
688263508Sdim  unsigned BPReg      = isPPC64 ? PPC::X30 : PPC::R30;
689263508Sdim  unsigned FPReg      = isPPC64 ? PPC::X31 : PPC::R31;
690263508Sdim  unsigned ScratchReg  = isPPC64 ? PPC::X0  : PPC::R0;
691263508Sdim  unsigned TempReg     = isPPC64 ? PPC::X12 : PPC::R12; // another scratch reg
692263508Sdim  const MCInstrDesc& MTLRInst = TII.get( isPPC64 ? PPC::MTLR8
693263508Sdim                                                 : PPC::MTLR );
694263508Sdim  const MCInstrDesc& LoadInst = TII.get( isPPC64 ? PPC::LD
695263508Sdim                                                 : PPC::LWZ );
696263508Sdim  const MCInstrDesc& LoadImmShiftedInst = TII.get( isPPC64 ? PPC::LIS8
697263508Sdim                                                           : PPC::LIS );
698263508Sdim  const MCInstrDesc& OrImmInst = TII.get( isPPC64 ? PPC::ORI8
699263508Sdim                                                  : PPC::ORI );
700263508Sdim  const MCInstrDesc& AddImmInst = TII.get( isPPC64 ? PPC::ADDI8
701263508Sdim                                                   : PPC::ADDI );
702263508Sdim  const MCInstrDesc& AddInst = TII.get( isPPC64 ? PPC::ADD8
703263508Sdim                                                : PPC::ADD4 );
704263508Sdim
705218885Sdim  int LROffset = PPCFrameLowering::getReturnSaveOffset(isPPC64, isDarwinABI);
706218885Sdim
707218885Sdim  int FPOffset = 0;
708218885Sdim  if (HasFP) {
709263508Sdim    if (isSVR4ABI) {
710218885Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
711218885Sdim      int FPIndex = FI->getFramePointerSaveIndex();
712218885Sdim      assert(FPIndex && "No Frame Pointer Save Slot!");
713218885Sdim      FPOffset = FFI->getObjectOffset(FPIndex);
714218885Sdim    } else {
715218885Sdim      FPOffset = PPCFrameLowering::getFramePointerSaveOffset(isPPC64, isDarwinABI);
716218885Sdim    }
717218885Sdim  }
718218885Sdim
719263508Sdim  int BPOffset = 0;
720263508Sdim  if (HasBP) {
721263508Sdim    if (isSVR4ABI) {
722263508Sdim      MachineFrameInfo *FFI = MF.getFrameInfo();
723263508Sdim      int BPIndex = FI->getBasePointerSaveIndex();
724263508Sdim      assert(BPIndex && "No Base Pointer Save Slot!");
725263508Sdim      BPOffset = FFI->getObjectOffset(BPIndex);
726263508Sdim    } else {
727263508Sdim      BPOffset =
728263508Sdim        PPCFrameLowering::getBasePointerSaveOffset(isPPC64, isDarwinABI);
729263508Sdim    }
730263508Sdim  }
731263508Sdim
732218885Sdim  bool UsesTCRet =  RetOpcode == PPC::TCRETURNri ||
733218885Sdim    RetOpcode == PPC::TCRETURNdi ||
734218885Sdim    RetOpcode == PPC::TCRETURNai ||
735218885Sdim    RetOpcode == PPC::TCRETURNri8 ||
736218885Sdim    RetOpcode == PPC::TCRETURNdi8 ||
737218885Sdim    RetOpcode == PPC::TCRETURNai8;
738218885Sdim
739218885Sdim  if (UsesTCRet) {
740218885Sdim    int MaxTCRetDelta = FI->getTailCallSPDelta();
741218885Sdim    MachineOperand &StackAdjust = MBBI->getOperand(1);
742218885Sdim    assert(StackAdjust.isImm() && "Expecting immediate value.");
743218885Sdim    // Adjust stack pointer.
744218885Sdim    int StackAdj = StackAdjust.getImm();
745218885Sdim    int Delta = StackAdj - MaxTCRetDelta;
746218885Sdim    assert((Delta >= 0) && "Delta must be positive");
747218885Sdim    if (MaxTCRetDelta>0)
748218885Sdim      FrameSize += (StackAdj +Delta);
749218885Sdim    else
750218885Sdim      FrameSize += StackAdj;
751218885Sdim  }
752218885Sdim
753263508Sdim  // Frames of 32KB & larger require special handling because they cannot be
754263508Sdim  // indexed into with a simple LD/LWZ immediate offset operand.
755263508Sdim  bool isLargeFrame = !isInt<16>(FrameSize);
756263508Sdim
757218885Sdim  if (FrameSize) {
758263508Sdim    // In the prologue, the loaded (or persistent) stack pointer value is offset
759263508Sdim    // by the STDU/STDUX/STWU/STWUX instruction.  Add this offset back now.
760263508Sdim
761263508Sdim    // If this function contained a fastcc call and GuaranteedTailCallOpt is
762263508Sdim    // enabled (=> hasFastCall()==true) the fastcc call might contain a tail
763263508Sdim    // call which invalidates the stack pointer value in SP(0). So we use the
764263508Sdim    // value of R31 in this case.
765263508Sdim    if (FI->hasFastCall()) {
766263508Sdim      assert(HasFP && "Expecting a valid frame pointer.");
767263508Sdim      if (!isLargeFrame) {
768263508Sdim        BuildMI(MBB, MBBI, dl, AddImmInst, SPReg)
769263508Sdim          .addReg(FPReg).addImm(FrameSize);
770263508Sdim      } else {
771263508Sdim        BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, ScratchReg)
772218885Sdim          .addImm(FrameSize >> 16);
773263508Sdim        BuildMI(MBB, MBBI, dl, OrImmInst, ScratchReg)
774263508Sdim          .addReg(ScratchReg, RegState::Kill)
775218885Sdim          .addImm(FrameSize & 0xFFFF);
776263508Sdim        BuildMI(MBB, MBBI, dl, AddInst)
777263508Sdim          .addReg(SPReg)
778263508Sdim          .addReg(FPReg)
779263508Sdim          .addReg(ScratchReg);
780218885Sdim      }
781263508Sdim    } else if (!isLargeFrame && !HasBP && !MFI->hasVarSizedObjects()) {
782263508Sdim      BuildMI(MBB, MBBI, dl, AddImmInst, SPReg)
783263508Sdim        .addReg(SPReg)
784263508Sdim        .addImm(FrameSize);
785218885Sdim    } else {
786263508Sdim      BuildMI(MBB, MBBI, dl, LoadInst, SPReg)
787263508Sdim        .addImm(0)
788263508Sdim        .addReg(SPReg);
789218885Sdim    }
790263508Sdim
791218885Sdim  }
792218885Sdim
793263508Sdim  if (MustSaveLR)
794263508Sdim    BuildMI(MBB, MBBI, dl, LoadInst, ScratchReg)
795263508Sdim      .addImm(LROffset)
796263508Sdim      .addReg(SPReg);
797218885Sdim
798263508Sdim  assert((isPPC64 || MustSaveCRs.empty()) &&
799263508Sdim         "Epilogue CR restoring supported only in 64-bit mode");
800251662Sdim
801263508Sdim  if (!MustSaveCRs.empty()) // will only occur for PPC64
802263508Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::LWZ8), TempReg)
803263508Sdim      .addImm(8)
804263508Sdim      .addReg(SPReg);
805218885Sdim
806263508Sdim  if (HasFP)
807263508Sdim    BuildMI(MBB, MBBI, dl, LoadInst, FPReg)
808263508Sdim      .addImm(FPOffset)
809263508Sdim      .addReg(SPReg);
810251662Sdim
811263508Sdim  if (HasBP)
812263508Sdim    BuildMI(MBB, MBBI, dl, LoadInst, BPReg)
813263508Sdim      .addImm(BPOffset)
814263508Sdim      .addReg(SPReg);
815218885Sdim
816263508Sdim  if (!MustSaveCRs.empty()) // will only occur for PPC64
817263508Sdim    for (unsigned i = 0, e = MustSaveCRs.size(); i != e; ++i)
818263508Sdim      BuildMI(MBB, MBBI, dl, TII.get(PPC::MTOCRF8), MustSaveCRs[i])
819263508Sdim        .addReg(TempReg, getKillRegState(i == e-1));
820251662Sdim
821263508Sdim  if (MustSaveLR)
822263508Sdim    BuildMI(MBB, MBBI, dl, MTLRInst).addReg(ScratchReg);
823218885Sdim
824218885Sdim  // Callee pop calling convention. Pop parameter/linkage area. Used for tail
825218885Sdim  // call optimization
826234353Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt && RetOpcode == PPC::BLR &&
827218885Sdim      MF.getFunction()->getCallingConv() == CallingConv::Fast) {
828218885Sdim     PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
829218885Sdim     unsigned CallerAllocatedAmt = FI->getMinReservedArea();
830218885Sdim
831218885Sdim     if (CallerAllocatedAmt && isInt<16>(CallerAllocatedAmt)) {
832263508Sdim       BuildMI(MBB, MBBI, dl, AddImmInst, SPReg)
833263508Sdim         .addReg(SPReg).addImm(CallerAllocatedAmt);
834218885Sdim     } else {
835263508Sdim       BuildMI(MBB, MBBI, dl, LoadImmShiftedInst, ScratchReg)
836218885Sdim          .addImm(CallerAllocatedAmt >> 16);
837263508Sdim       BuildMI(MBB, MBBI, dl, OrImmInst, ScratchReg)
838263508Sdim          .addReg(ScratchReg, RegState::Kill)
839218885Sdim          .addImm(CallerAllocatedAmt & 0xFFFF);
840263508Sdim       BuildMI(MBB, MBBI, dl, AddInst)
841263508Sdim          .addReg(SPReg)
842218885Sdim          .addReg(FPReg)
843263508Sdim          .addReg(ScratchReg);
844218885Sdim     }
845218885Sdim  } else if (RetOpcode == PPC::TCRETURNdi) {
846218885Sdim    MBBI = MBB.getLastNonDebugInstr();
847218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
848218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILB)).
849218885Sdim      addGlobalAddress(JumpTarget.getGlobal(), JumpTarget.getOffset());
850218885Sdim  } else if (RetOpcode == PPC::TCRETURNri) {
851218885Sdim    MBBI = MBB.getLastNonDebugInstr();
852218885Sdim    assert(MBBI->getOperand(0).isReg() && "Expecting register operand.");
853218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBCTR));
854218885Sdim  } else if (RetOpcode == PPC::TCRETURNai) {
855218885Sdim    MBBI = MBB.getLastNonDebugInstr();
856218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
857218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBA)).addImm(JumpTarget.getImm());
858218885Sdim  } else if (RetOpcode == PPC::TCRETURNdi8) {
859218885Sdim    MBBI = MBB.getLastNonDebugInstr();
860218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
861218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILB8)).
862218885Sdim      addGlobalAddress(JumpTarget.getGlobal(), JumpTarget.getOffset());
863218885Sdim  } else if (RetOpcode == PPC::TCRETURNri8) {
864218885Sdim    MBBI = MBB.getLastNonDebugInstr();
865218885Sdim    assert(MBBI->getOperand(0).isReg() && "Expecting register operand.");
866218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBCTR8));
867218885Sdim  } else if (RetOpcode == PPC::TCRETURNai8) {
868218885Sdim    MBBI = MBB.getLastNonDebugInstr();
869218885Sdim    MachineOperand &JumpTarget = MBBI->getOperand(0);
870218885Sdim    BuildMI(MBB, MBBI, dl, TII.get(PPC::TAILBA8)).addImm(JumpTarget.getImm());
871218885Sdim  }
872218885Sdim}
873218885Sdim
874218885Sdim/// MustSaveLR - Return true if this function requires that we save the LR
875218885Sdim/// register onto the stack in the prolog and restore it in the epilog of the
876218885Sdim/// function.
877218885Sdimstatic bool MustSaveLR(const MachineFunction &MF, unsigned LR) {
878218885Sdim  const PPCFunctionInfo *MFI = MF.getInfo<PPCFunctionInfo>();
879218885Sdim
880218885Sdim  // We need a save/restore of LR if there is any def of LR (which is
881218885Sdim  // defined by calls, including the PIC setup sequence), or if there is
882218885Sdim  // some use of the LR stack slot (e.g. for builtin_return_address).
883218885Sdim  // (LR comes in 32 and 64 bit versions.)
884218885Sdim  MachineRegisterInfo::def_iterator RI = MF.getRegInfo().def_begin(LR);
885218885Sdim  return RI !=MF.getRegInfo().def_end() || MFI->isLRStoreRequired();
886218885Sdim}
887218885Sdim
888218885Sdimvoid
889218885SdimPPCFrameLowering::processFunctionBeforeCalleeSavedScan(MachineFunction &MF,
890249423Sdim                                                   RegScavenger *) const {
891263508Sdim  const PPCRegisterInfo *RegInfo =
892263508Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
893218885Sdim
894218885Sdim  //  Save and clear the LR state.
895218885Sdim  PPCFunctionInfo *FI = MF.getInfo<PPCFunctionInfo>();
896218885Sdim  unsigned LR = RegInfo->getRARegister();
897218885Sdim  FI->setMustSaveLR(MustSaveLR(MF, LR));
898249423Sdim  MachineRegisterInfo &MRI = MF.getRegInfo();
899249423Sdim  MRI.setPhysRegUnused(LR);
900218885Sdim
901218885Sdim  //  Save R31 if necessary
902218885Sdim  int FPSI = FI->getFramePointerSaveIndex();
903218885Sdim  bool isPPC64 = Subtarget.isPPC64();
904218885Sdim  bool isDarwinABI  = Subtarget.isDarwinABI();
905218885Sdim  MachineFrameInfo *MFI = MF.getFrameInfo();
906218885Sdim
907218885Sdim  // If the frame pointer save index hasn't been defined yet.
908218885Sdim  if (!FPSI && needsFP(MF)) {
909218885Sdim    // Find out what the fix offset of the frame pointer save area.
910218885Sdim    int FPOffset = getFramePointerSaveOffset(isPPC64, isDarwinABI);
911218885Sdim    // Allocate the frame index for frame pointer save area.
912218885Sdim    FPSI = MFI->CreateFixedObject(isPPC64? 8 : 4, FPOffset, true);
913218885Sdim    // Save the result.
914218885Sdim    FI->setFramePointerSaveIndex(FPSI);
915218885Sdim  }
916218885Sdim
917263508Sdim  int BPSI = FI->getBasePointerSaveIndex();
918263508Sdim  if (!BPSI && RegInfo->hasBasePointer(MF)) {
919263508Sdim    int BPOffset = getBasePointerSaveOffset(isPPC64, isDarwinABI);
920263508Sdim    // Allocate the frame index for the base pointer save area.
921263508Sdim    BPSI = MFI->CreateFixedObject(isPPC64? 8 : 4, BPOffset, true);
922263508Sdim    // Save the result.
923263508Sdim    FI->setBasePointerSaveIndex(BPSI);
924263508Sdim  }
925263508Sdim
926218885Sdim  // Reserve stack space to move the linkage area to in case of a tail call.
927218885Sdim  int TCSPDelta = 0;
928234353Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt &&
929234353Sdim      (TCSPDelta = FI->getTailCallSPDelta()) < 0) {
930218885Sdim    MFI->CreateFixedObject(-1 * TCSPDelta, TCSPDelta, true);
931218885Sdim  }
932218885Sdim
933249423Sdim  // For 32-bit SVR4, allocate the nonvolatile CR spill slot iff the
934249423Sdim  // function uses CR 2, 3, or 4.
935249423Sdim  if (!isPPC64 && !isDarwinABI &&
936249423Sdim      (MRI.isPhysRegUsed(PPC::CR2) ||
937249423Sdim       MRI.isPhysRegUsed(PPC::CR3) ||
938249423Sdim       MRI.isPhysRegUsed(PPC::CR4))) {
939249423Sdim    int FrameIdx = MFI->CreateFixedObject((uint64_t)4, (int64_t)-4, true);
940249423Sdim    FI->setCRSpillFrameIndex(FrameIdx);
941249423Sdim  }
942218885Sdim}
943218885Sdim
944249423Sdimvoid PPCFrameLowering::processFunctionBeforeFrameFinalized(MachineFunction &MF,
945249423Sdim                                                       RegScavenger *RS) const {
946218885Sdim  // Early exit if not using the SVR4 ABI.
947249423Sdim  if (!Subtarget.isSVR4ABI()) {
948249423Sdim    addScavengingSpillSlot(MF, RS);
949218885Sdim    return;
950249423Sdim  }
951218885Sdim
952218885Sdim  // Get callee saved register information.
953218885Sdim  MachineFrameInfo *FFI = MF.getFrameInfo();
954218885Sdim  const std::vector<CalleeSavedInfo> &CSI = FFI->getCalleeSavedInfo();
955218885Sdim
956218885Sdim  // Early exit if no callee saved registers are modified!
957218885Sdim  if (CSI.empty() && !needsFP(MF)) {
958249423Sdim    addScavengingSpillSlot(MF, RS);
959218885Sdim    return;
960218885Sdim  }
961218885Sdim
962218885Sdim  unsigned MinGPR = PPC::R31;
963218885Sdim  unsigned MinG8R = PPC::X31;
964218885Sdim  unsigned MinFPR = PPC::F31;
965218885Sdim  unsigned MinVR = PPC::V31;
966218885Sdim
967218885Sdim  bool HasGPSaveArea = false;
968218885Sdim  bool HasG8SaveArea = false;
969218885Sdim  bool HasFPSaveArea = false;
970218885Sdim  bool HasVRSAVESaveArea = false;
971218885Sdim  bool HasVRSaveArea = false;
972218885Sdim
973218885Sdim  SmallVector<CalleeSavedInfo, 18> GPRegs;
974218885Sdim  SmallVector<CalleeSavedInfo, 18> G8Regs;
975218885Sdim  SmallVector<CalleeSavedInfo, 18> FPRegs;
976218885Sdim  SmallVector<CalleeSavedInfo, 18> VRegs;
977218885Sdim
978218885Sdim  for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
979218885Sdim    unsigned Reg = CSI[i].getReg();
980239462Sdim    if (PPC::GPRCRegClass.contains(Reg)) {
981218885Sdim      HasGPSaveArea = true;
982218885Sdim
983218885Sdim      GPRegs.push_back(CSI[i]);
984218885Sdim
985218885Sdim      if (Reg < MinGPR) {
986218885Sdim        MinGPR = Reg;
987218885Sdim      }
988239462Sdim    } else if (PPC::G8RCRegClass.contains(Reg)) {
989218885Sdim      HasG8SaveArea = true;
990218885Sdim
991218885Sdim      G8Regs.push_back(CSI[i]);
992218885Sdim
993218885Sdim      if (Reg < MinG8R) {
994218885Sdim        MinG8R = Reg;
995218885Sdim      }
996239462Sdim    } else if (PPC::F8RCRegClass.contains(Reg)) {
997218885Sdim      HasFPSaveArea = true;
998218885Sdim
999218885Sdim      FPRegs.push_back(CSI[i]);
1000218885Sdim
1001218885Sdim      if (Reg < MinFPR) {
1002218885Sdim        MinFPR = Reg;
1003218885Sdim      }
1004239462Sdim    } else if (PPC::CRBITRCRegClass.contains(Reg) ||
1005239462Sdim               PPC::CRRCRegClass.contains(Reg)) {
1006243830Sdim      ; // do nothing, as we already know whether CRs are spilled
1007239462Sdim    } else if (PPC::VRSAVERCRegClass.contains(Reg)) {
1008218885Sdim      HasVRSAVESaveArea = true;
1009239462Sdim    } else if (PPC::VRRCRegClass.contains(Reg)) {
1010218885Sdim      HasVRSaveArea = true;
1011218885Sdim
1012218885Sdim      VRegs.push_back(CSI[i]);
1013218885Sdim
1014218885Sdim      if (Reg < MinVR) {
1015218885Sdim        MinVR = Reg;
1016218885Sdim      }
1017218885Sdim    } else {
1018218885Sdim      llvm_unreachable("Unknown RegisterClass!");
1019218885Sdim    }
1020218885Sdim  }
1021218885Sdim
1022218885Sdim  PPCFunctionInfo *PFI = MF.getInfo<PPCFunctionInfo>();
1023249423Sdim  const TargetRegisterInfo *TRI = MF.getTarget().getRegisterInfo();
1024218885Sdim
1025218885Sdim  int64_t LowerBound = 0;
1026218885Sdim
1027218885Sdim  // Take into account stack space reserved for tail calls.
1028218885Sdim  int TCSPDelta = 0;
1029234353Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt &&
1030234353Sdim      (TCSPDelta = PFI->getTailCallSPDelta()) < 0) {
1031218885Sdim    LowerBound = TCSPDelta;
1032218885Sdim  }
1033218885Sdim
1034218885Sdim  // The Floating-point register save area is right below the back chain word
1035218885Sdim  // of the previous stack frame.
1036218885Sdim  if (HasFPSaveArea) {
1037218885Sdim    for (unsigned i = 0, e = FPRegs.size(); i != e; ++i) {
1038218885Sdim      int FI = FPRegs[i].getFrameIdx();
1039218885Sdim
1040218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1041218885Sdim    }
1042218885Sdim
1043249423Sdim    LowerBound -= (31 - TRI->getEncodingValue(MinFPR) + 1) * 8;
1044218885Sdim  }
1045218885Sdim
1046218885Sdim  // Check whether the frame pointer register is allocated. If so, make sure it
1047218885Sdim  // is spilled to the correct offset.
1048218885Sdim  if (needsFP(MF)) {
1049218885Sdim    HasGPSaveArea = true;
1050218885Sdim
1051218885Sdim    int FI = PFI->getFramePointerSaveIndex();
1052218885Sdim    assert(FI && "No Frame Pointer Save Slot!");
1053218885Sdim
1054218885Sdim    FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1055218885Sdim  }
1056218885Sdim
1057263508Sdim  const PPCRegisterInfo *RegInfo =
1058263508Sdim    static_cast<const PPCRegisterInfo*>(MF.getTarget().getRegisterInfo());
1059263508Sdim  if (RegInfo->hasBasePointer(MF)) {
1060263508Sdim    HasGPSaveArea = true;
1061263508Sdim
1062263508Sdim    int FI = PFI->getBasePointerSaveIndex();
1063263508Sdim    assert(FI && "No Base Pointer Save Slot!");
1064263508Sdim
1065263508Sdim    FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1066263508Sdim  }
1067263508Sdim
1068218885Sdim  // General register save area starts right below the Floating-point
1069218885Sdim  // register save area.
1070218885Sdim  if (HasGPSaveArea || HasG8SaveArea) {
1071218885Sdim    // Move general register save area spill slots down, taking into account
1072218885Sdim    // the size of the Floating-point register save area.
1073218885Sdim    for (unsigned i = 0, e = GPRegs.size(); i != e; ++i) {
1074218885Sdim      int FI = GPRegs[i].getFrameIdx();
1075218885Sdim
1076218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1077218885Sdim    }
1078218885Sdim
1079218885Sdim    // Move general register save area spill slots down, taking into account
1080218885Sdim    // the size of the Floating-point register save area.
1081218885Sdim    for (unsigned i = 0, e = G8Regs.size(); i != e; ++i) {
1082218885Sdim      int FI = G8Regs[i].getFrameIdx();
1083218885Sdim
1084218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1085218885Sdim    }
1086218885Sdim
1087218885Sdim    unsigned MinReg =
1088249423Sdim      std::min<unsigned>(TRI->getEncodingValue(MinGPR),
1089249423Sdim                         TRI->getEncodingValue(MinG8R));
1090218885Sdim
1091218885Sdim    if (Subtarget.isPPC64()) {
1092218885Sdim      LowerBound -= (31 - MinReg + 1) * 8;
1093218885Sdim    } else {
1094218885Sdim      LowerBound -= (31 - MinReg + 1) * 4;
1095218885Sdim    }
1096218885Sdim  }
1097218885Sdim
1098243830Sdim  // For 32-bit only, the CR save area is below the general register
1099243830Sdim  // save area.  For 64-bit SVR4, the CR save area is addressed relative
1100243830Sdim  // to the stack pointer and hence does not need an adjustment here.
1101243830Sdim  // Only CR2 (the first nonvolatile spilled) has an associated frame
1102243830Sdim  // index so that we have a single uniform save area.
1103243830Sdim  if (spillsCR(MF) && !(Subtarget.isPPC64() && Subtarget.isSVR4ABI())) {
1104218885Sdim    // Adjust the frame index of the CR spill slot.
1105218885Sdim    for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1106218885Sdim      unsigned Reg = CSI[i].getReg();
1107218885Sdim
1108243830Sdim      if ((Subtarget.isSVR4ABI() && Reg == PPC::CR2)
1109243830Sdim	  // Leave Darwin logic as-is.
1110243830Sdim	  || (!Subtarget.isSVR4ABI() &&
1111243830Sdim	      (PPC::CRBITRCRegClass.contains(Reg) ||
1112243830Sdim	       PPC::CRRCRegClass.contains(Reg)))) {
1113218885Sdim        int FI = CSI[i].getFrameIdx();
1114218885Sdim
1115218885Sdim        FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1116218885Sdim      }
1117218885Sdim    }
1118218885Sdim
1119218885Sdim    LowerBound -= 4; // The CR save area is always 4 bytes long.
1120218885Sdim  }
1121218885Sdim
1122218885Sdim  if (HasVRSAVESaveArea) {
1123218885Sdim    // FIXME SVR4: Is it actually possible to have multiple elements in CSI
1124218885Sdim    //             which have the VRSAVE register class?
1125218885Sdim    // Adjust the frame index of the VRSAVE spill slot.
1126218885Sdim    for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1127218885Sdim      unsigned Reg = CSI[i].getReg();
1128218885Sdim
1129239462Sdim      if (PPC::VRSAVERCRegClass.contains(Reg)) {
1130218885Sdim        int FI = CSI[i].getFrameIdx();
1131218885Sdim
1132218885Sdim        FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1133218885Sdim      }
1134218885Sdim    }
1135218885Sdim
1136218885Sdim    LowerBound -= 4; // The VRSAVE save area is always 4 bytes long.
1137218885Sdim  }
1138218885Sdim
1139218885Sdim  if (HasVRSaveArea) {
1140218885Sdim    // Insert alignment padding, we need 16-byte alignment.
1141218885Sdim    LowerBound = (LowerBound - 15) & ~(15);
1142218885Sdim
1143218885Sdim    for (unsigned i = 0, e = VRegs.size(); i != e; ++i) {
1144218885Sdim      int FI = VRegs[i].getFrameIdx();
1145218885Sdim
1146218885Sdim      FFI->setObjectOffset(FI, LowerBound + FFI->getObjectOffset(FI));
1147218885Sdim    }
1148218885Sdim  }
1149249423Sdim
1150249423Sdim  addScavengingSpillSlot(MF, RS);
1151218885Sdim}
1152243830Sdim
1153249423Sdimvoid
1154249423SdimPPCFrameLowering::addScavengingSpillSlot(MachineFunction &MF,
1155249423Sdim                                         RegScavenger *RS) const {
1156249423Sdim  // Reserve a slot closest to SP or frame pointer if we have a dynalloc or
1157249423Sdim  // a large stack, which will require scavenging a register to materialize a
1158249423Sdim  // large offset.
1159249423Sdim
1160249423Sdim  // We need to have a scavenger spill slot for spills if the frame size is
1161249423Sdim  // large. In case there is no free register for large-offset addressing,
1162249423Sdim  // this slot is used for the necessary emergency spill. Also, we need the
1163249423Sdim  // slot for dynamic stack allocations.
1164249423Sdim
1165249423Sdim  // The scavenger might be invoked if the frame offset does not fit into
1166249423Sdim  // the 16-bit immediate. We don't know the complete frame size here
1167249423Sdim  // because we've not yet computed callee-saved register spills or the
1168249423Sdim  // needed alignment padding.
1169249423Sdim  unsigned StackSize = determineFrameLayout(MF, false, true);
1170249423Sdim  MachineFrameInfo *MFI = MF.getFrameInfo();
1171249423Sdim  if (MFI->hasVarSizedObjects() || spillsCR(MF) || spillsVRSAVE(MF) ||
1172249423Sdim      hasNonRISpills(MF) || (hasSpills(MF) && !isInt<16>(StackSize))) {
1173249423Sdim    const TargetRegisterClass *GPRC = &PPC::GPRCRegClass;
1174249423Sdim    const TargetRegisterClass *G8RC = &PPC::G8RCRegClass;
1175249423Sdim    const TargetRegisterClass *RC = Subtarget.isPPC64() ? G8RC : GPRC;
1176249423Sdim    RS->addScavengingFrameIndex(MFI->CreateStackObject(RC->getSize(),
1177249423Sdim                                                       RC->getAlignment(),
1178249423Sdim                                                       false));
1179249423Sdim
1180263508Sdim    // Might we have over-aligned allocas?
1181263508Sdim    bool HasAlVars = MFI->hasVarSizedObjects() &&
1182263508Sdim                     MFI->getMaxAlignment() > getStackAlignment();
1183263508Sdim
1184249423Sdim    // These kinds of spills might need two registers.
1185263508Sdim    if (spillsCR(MF) || spillsVRSAVE(MF) || HasAlVars)
1186249423Sdim      RS->addScavengingFrameIndex(MFI->CreateStackObject(RC->getSize(),
1187249423Sdim                                                         RC->getAlignment(),
1188249423Sdim                                                         false));
1189249423Sdim
1190249423Sdim  }
1191249423Sdim}
1192249423Sdim
1193243830Sdimbool
1194243830SdimPPCFrameLowering::spillCalleeSavedRegisters(MachineBasicBlock &MBB,
1195243830Sdim				     MachineBasicBlock::iterator MI,
1196243830Sdim				     const std::vector<CalleeSavedInfo> &CSI,
1197243830Sdim				     const TargetRegisterInfo *TRI) const {
1198243830Sdim
1199243830Sdim  // Currently, this function only handles SVR4 32- and 64-bit ABIs.
1200243830Sdim  // Return false otherwise to maintain pre-existing behavior.
1201243830Sdim  if (!Subtarget.isSVR4ABI())
1202243830Sdim    return false;
1203243830Sdim
1204243830Sdim  MachineFunction *MF = MBB.getParent();
1205243830Sdim  const PPCInstrInfo &TII =
1206243830Sdim    *static_cast<const PPCInstrInfo*>(MF->getTarget().getInstrInfo());
1207243830Sdim  DebugLoc DL;
1208243830Sdim  bool CRSpilled = false;
1209251662Sdim  MachineInstrBuilder CRMIB;
1210243830Sdim
1211243830Sdim  for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1212243830Sdim    unsigned Reg = CSI[i].getReg();
1213263508Sdim    // Only Darwin actually uses the VRSAVE register, but it can still appear
1214263508Sdim    // here if, for example, @llvm.eh.unwind.init() is used.  If we're not on
1215263508Sdim    // Darwin, ignore it.
1216263508Sdim    if (Reg == PPC::VRSAVE && !Subtarget.isDarwinABI())
1217263508Sdim      continue;
1218263508Sdim
1219243830Sdim    // CR2 through CR4 are the nonvolatile CR fields.
1220243830Sdim    bool IsCRField = PPC::CR2 <= Reg && Reg <= PPC::CR4;
1221243830Sdim
1222243830Sdim    // Add the callee-saved register as live-in; it's killed at the spill.
1223243830Sdim    MBB.addLiveIn(Reg);
1224243830Sdim
1225251662Sdim    if (CRSpilled && IsCRField) {
1226251662Sdim      CRMIB.addReg(Reg, RegState::ImplicitKill);
1227251662Sdim      continue;
1228251662Sdim    }
1229251662Sdim
1230243830Sdim    // Insert the spill to the stack frame.
1231243830Sdim    if (IsCRField) {
1232251662Sdim      PPCFunctionInfo *FuncInfo = MF->getInfo<PPCFunctionInfo>();
1233243830Sdim      if (Subtarget.isPPC64()) {
1234251662Sdim        // The actual spill will happen at the start of the prologue.
1235251662Sdim        FuncInfo->addMustSaveCR(Reg);
1236243830Sdim      } else {
1237251662Sdim        CRSpilled = true;
1238251662Sdim        FuncInfo->setSpillsCR();
1239251662Sdim
1240243830Sdim	// 32-bit:  FP-relative.  Note that we made sure CR2-CR4 all have
1241243830Sdim	// the same frame index in PPCRegisterInfo::hasReservedSpillSlot.
1242251662Sdim	CRMIB = BuildMI(*MF, DL, TII.get(PPC::MFCR), PPC::R12)
1243251662Sdim                  .addReg(Reg, RegState::ImplicitKill);
1244251662Sdim
1245251662Sdim	MBB.insert(MI, CRMIB);
1246243830Sdim	MBB.insert(MI, addFrameReference(BuildMI(*MF, DL, TII.get(PPC::STW))
1247243830Sdim					 .addReg(PPC::R12,
1248243830Sdim						 getKillRegState(true)),
1249243830Sdim					 CSI[i].getFrameIdx()));
1250243830Sdim      }
1251243830Sdim    } else {
1252243830Sdim      const TargetRegisterClass *RC = TRI->getMinimalPhysRegClass(Reg);
1253243830Sdim      TII.storeRegToStackSlot(MBB, MI, Reg, true,
1254243830Sdim			      CSI[i].getFrameIdx(), RC, TRI);
1255243830Sdim    }
1256243830Sdim  }
1257243830Sdim  return true;
1258243830Sdim}
1259243830Sdim
1260243830Sdimstatic void
1261251662SdimrestoreCRs(bool isPPC64, bool is31,
1262251662Sdim           bool CR2Spilled, bool CR3Spilled, bool CR4Spilled,
1263243830Sdim	   MachineBasicBlock &MBB, MachineBasicBlock::iterator MI,
1264243830Sdim	   const std::vector<CalleeSavedInfo> &CSI, unsigned CSIIndex) {
1265243830Sdim
1266243830Sdim  MachineFunction *MF = MBB.getParent();
1267243830Sdim  const PPCInstrInfo &TII =
1268243830Sdim    *static_cast<const PPCInstrInfo*>(MF->getTarget().getInstrInfo());
1269243830Sdim  DebugLoc DL;
1270243830Sdim  unsigned RestoreOp, MoveReg;
1271243830Sdim
1272251662Sdim  if (isPPC64)
1273251662Sdim    // This is handled during epilogue generation.
1274251662Sdim    return;
1275251662Sdim  else {
1276243830Sdim    // 32-bit:  FP-relative
1277243830Sdim    MBB.insert(MI, addFrameReference(BuildMI(*MF, DL, TII.get(PPC::LWZ),
1278243830Sdim					     PPC::R12),
1279243830Sdim				     CSI[CSIIndex].getFrameIdx()));
1280263508Sdim    RestoreOp = PPC::MTOCRF;
1281243830Sdim    MoveReg = PPC::R12;
1282243830Sdim  }
1283243830Sdim
1284243830Sdim  if (CR2Spilled)
1285243830Sdim    MBB.insert(MI, BuildMI(*MF, DL, TII.get(RestoreOp), PPC::CR2)
1286249423Sdim               .addReg(MoveReg, getKillRegState(!CR3Spilled && !CR4Spilled)));
1287243830Sdim
1288243830Sdim  if (CR3Spilled)
1289243830Sdim    MBB.insert(MI, BuildMI(*MF, DL, TII.get(RestoreOp), PPC::CR3)
1290249423Sdim               .addReg(MoveReg, getKillRegState(!CR4Spilled)));
1291243830Sdim
1292243830Sdim  if (CR4Spilled)
1293243830Sdim    MBB.insert(MI, BuildMI(*MF, DL, TII.get(RestoreOp), PPC::CR4)
1294249423Sdim               .addReg(MoveReg, getKillRegState(true)));
1295243830Sdim}
1296243830Sdim
1297249423Sdimvoid PPCFrameLowering::
1298249423SdimeliminateCallFramePseudoInstr(MachineFunction &MF, MachineBasicBlock &MBB,
1299249423Sdim                              MachineBasicBlock::iterator I) const {
1300249423Sdim  const PPCInstrInfo &TII =
1301249423Sdim    *static_cast<const PPCInstrInfo*>(MF.getTarget().getInstrInfo());
1302249423Sdim  if (MF.getTarget().Options.GuaranteedTailCallOpt &&
1303249423Sdim      I->getOpcode() == PPC::ADJCALLSTACKUP) {
1304249423Sdim    // Add (actually subtract) back the amount the callee popped on return.
1305249423Sdim    if (int CalleeAmt =  I->getOperand(1).getImm()) {
1306249423Sdim      bool is64Bit = Subtarget.isPPC64();
1307249423Sdim      CalleeAmt *= -1;
1308249423Sdim      unsigned StackReg = is64Bit ? PPC::X1 : PPC::R1;
1309249423Sdim      unsigned TmpReg = is64Bit ? PPC::X0 : PPC::R0;
1310249423Sdim      unsigned ADDIInstr = is64Bit ? PPC::ADDI8 : PPC::ADDI;
1311249423Sdim      unsigned ADDInstr = is64Bit ? PPC::ADD8 : PPC::ADD4;
1312249423Sdim      unsigned LISInstr = is64Bit ? PPC::LIS8 : PPC::LIS;
1313249423Sdim      unsigned ORIInstr = is64Bit ? PPC::ORI8 : PPC::ORI;
1314249423Sdim      MachineInstr *MI = I;
1315249423Sdim      DebugLoc dl = MI->getDebugLoc();
1316249423Sdim
1317249423Sdim      if (isInt<16>(CalleeAmt)) {
1318249423Sdim        BuildMI(MBB, I, dl, TII.get(ADDIInstr), StackReg)
1319249423Sdim          .addReg(StackReg, RegState::Kill)
1320249423Sdim          .addImm(CalleeAmt);
1321249423Sdim      } else {
1322249423Sdim        MachineBasicBlock::iterator MBBI = I;
1323249423Sdim        BuildMI(MBB, MBBI, dl, TII.get(LISInstr), TmpReg)
1324249423Sdim          .addImm(CalleeAmt >> 16);
1325249423Sdim        BuildMI(MBB, MBBI, dl, TII.get(ORIInstr), TmpReg)
1326249423Sdim          .addReg(TmpReg, RegState::Kill)
1327249423Sdim          .addImm(CalleeAmt & 0xFFFF);
1328249423Sdim        BuildMI(MBB, MBBI, dl, TII.get(ADDInstr), StackReg)
1329249423Sdim          .addReg(StackReg, RegState::Kill)
1330249423Sdim          .addReg(TmpReg);
1331249423Sdim      }
1332249423Sdim    }
1333249423Sdim  }
1334249423Sdim  // Simply discard ADJCALLSTACKDOWN, ADJCALLSTACKUP instructions.
1335249423Sdim  MBB.erase(I);
1336249423Sdim}
1337249423Sdim
1338243830Sdimbool
1339243830SdimPPCFrameLowering::restoreCalleeSavedRegisters(MachineBasicBlock &MBB,
1340243830Sdim					MachineBasicBlock::iterator MI,
1341243830Sdim				        const std::vector<CalleeSavedInfo> &CSI,
1342243830Sdim					const TargetRegisterInfo *TRI) const {
1343243830Sdim
1344243830Sdim  // Currently, this function only handles SVR4 32- and 64-bit ABIs.
1345243830Sdim  // Return false otherwise to maintain pre-existing behavior.
1346243830Sdim  if (!Subtarget.isSVR4ABI())
1347243830Sdim    return false;
1348243830Sdim
1349243830Sdim  MachineFunction *MF = MBB.getParent();
1350243830Sdim  const PPCInstrInfo &TII =
1351243830Sdim    *static_cast<const PPCInstrInfo*>(MF->getTarget().getInstrInfo());
1352243830Sdim  bool CR2Spilled = false;
1353243830Sdim  bool CR3Spilled = false;
1354243830Sdim  bool CR4Spilled = false;
1355243830Sdim  unsigned CSIIndex = 0;
1356243830Sdim
1357243830Sdim  // Initialize insertion-point logic; we will be restoring in reverse
1358243830Sdim  // order of spill.
1359243830Sdim  MachineBasicBlock::iterator I = MI, BeforeI = I;
1360243830Sdim  bool AtStart = I == MBB.begin();
1361243830Sdim
1362243830Sdim  if (!AtStart)
1363243830Sdim    --BeforeI;
1364243830Sdim
1365243830Sdim  for (unsigned i = 0, e = CSI.size(); i != e; ++i) {
1366243830Sdim    unsigned Reg = CSI[i].getReg();
1367243830Sdim
1368263508Sdim    // Only Darwin actually uses the VRSAVE register, but it can still appear
1369263508Sdim    // here if, for example, @llvm.eh.unwind.init() is used.  If we're not on
1370263508Sdim    // Darwin, ignore it.
1371263508Sdim    if (Reg == PPC::VRSAVE && !Subtarget.isDarwinABI())
1372263508Sdim      continue;
1373263508Sdim
1374243830Sdim    if (Reg == PPC::CR2) {
1375243830Sdim      CR2Spilled = true;
1376243830Sdim      // The spill slot is associated only with CR2, which is the
1377243830Sdim      // first nonvolatile spilled.  Save it here.
1378243830Sdim      CSIIndex = i;
1379243830Sdim      continue;
1380243830Sdim    } else if (Reg == PPC::CR3) {
1381243830Sdim      CR3Spilled = true;
1382243830Sdim      continue;
1383243830Sdim    } else if (Reg == PPC::CR4) {
1384243830Sdim      CR4Spilled = true;
1385243830Sdim      continue;
1386243830Sdim    } else {
1387243830Sdim      // When we first encounter a non-CR register after seeing at
1388243830Sdim      // least one CR register, restore all spilled CRs together.
1389243830Sdim      if ((CR2Spilled || CR3Spilled || CR4Spilled)
1390243830Sdim	  && !(PPC::CR2 <= Reg && Reg <= PPC::CR4)) {
1391251662Sdim        bool is31 = needsFP(*MF);
1392251662Sdim        restoreCRs(Subtarget.isPPC64(), is31,
1393251662Sdim                   CR2Spilled, CR3Spilled, CR4Spilled,
1394243830Sdim		   MBB, I, CSI, CSIIndex);
1395243830Sdim	CR2Spilled = CR3Spilled = CR4Spilled = false;
1396243830Sdim      }
1397243830Sdim
1398243830Sdim      // Default behavior for non-CR saves.
1399243830Sdim      const TargetRegisterClass *RC = TRI->getMinimalPhysRegClass(Reg);
1400243830Sdim      TII.loadRegFromStackSlot(MBB, I, Reg, CSI[i].getFrameIdx(),
1401243830Sdim			       RC, TRI);
1402243830Sdim      assert(I != MBB.begin() &&
1403243830Sdim	     "loadRegFromStackSlot didn't insert any code!");
1404243830Sdim      }
1405243830Sdim
1406243830Sdim    // Insert in reverse order.
1407243830Sdim    if (AtStart)
1408243830Sdim      I = MBB.begin();
1409243830Sdim    else {
1410243830Sdim      I = BeforeI;
1411243830Sdim      ++I;
1412243830Sdim    }
1413243830Sdim  }
1414243830Sdim
1415243830Sdim  // If we haven't yet spilled the CRs, do so now.
1416251662Sdim  if (CR2Spilled || CR3Spilled || CR4Spilled) {
1417251662Sdim    bool is31 = needsFP(*MF);
1418251662Sdim    restoreCRs(Subtarget.isPPC64(), is31, CR2Spilled, CR3Spilled, CR4Spilled,
1419243830Sdim	       MBB, I, CSI, CSIIndex);
1420251662Sdim  }
1421243830Sdim
1422243830Sdim  return true;
1423243830Sdim}
1424243830Sdim
1425