1 //===-------- LegalizeFloatTypes.cpp - Legalization of float types --------===//
2 //
3 // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 // See https://llvm.org/LICENSE.txt for license information.
5 // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6 //
7 //===----------------------------------------------------------------------===//
8 //
9 // This file implements float type expansion and softening for LegalizeTypes.
10 // Softening is the act of turning a computation in an illegal floating point
11 // type into a computation in an integer type of the same size; also known as
12 // "soft float".  For example, turning f32 arithmetic into operations using i32.
13 // The resulting integer value is the same as what you would get by performing
14 // the floating point operation and bitcasting the result to the integer type.
15 // Expansion is the act of changing a computation in an illegal type to be a
16 // computation in two identical registers of a smaller type.  For example,
17 // implementing ppcf128 arithmetic in two f64 registers.
18 //
19 //===----------------------------------------------------------------------===//
20 
21 #include "LegalizeTypes.h"
22 #include "llvm/Support/ErrorHandling.h"
23 #include "llvm/Support/raw_ostream.h"
24 using namespace llvm;
25 
26 #define DEBUG_TYPE "legalize-types"
27 
28 /// GetFPLibCall - Return the right libcall for the given floating point type.
29 static RTLIB::Libcall GetFPLibCall(EVT VT,
30                                    RTLIB::Libcall Call_F32,
31                                    RTLIB::Libcall Call_F64,
32                                    RTLIB::Libcall Call_F80,
33                                    RTLIB::Libcall Call_F128,
34                                    RTLIB::Libcall Call_PPCF128) {
35   return
36     VT == MVT::f32 ? Call_F32 :
37     VT == MVT::f64 ? Call_F64 :
38     VT == MVT::f80 ? Call_F80 :
39     VT == MVT::f128 ? Call_F128 :
40     VT == MVT::ppcf128 ? Call_PPCF128 :
41     RTLIB::UNKNOWN_LIBCALL;
42 }
43 
44 //===----------------------------------------------------------------------===//
45 //  Convert Float Results to Integer
46 //===----------------------------------------------------------------------===//
47 
48 void DAGTypeLegalizer::SoftenFloatResult(SDNode *N, unsigned ResNo) {
49   LLVM_DEBUG(dbgs() << "Soften float result " << ResNo << ": "; N->dump(&DAG);
50              dbgs() << "\n");
51   SDValue R = SDValue();
52 
53   switch (N->getOpcode()) {
54   default:
55 #ifndef NDEBUG
56     dbgs() << "SoftenFloatResult #" << ResNo << ": ";
57     N->dump(&DAG); dbgs() << "\n";
58 #endif
59     llvm_unreachable("Do not know how to soften the result of this operator!");
60 
61     case ISD::MERGE_VALUES:R = SoftenFloatRes_MERGE_VALUES(N, ResNo); break;
62     case ISD::BITCAST:     R = SoftenFloatRes_BITCAST(N); break;
63     case ISD::BUILD_PAIR:  R = SoftenFloatRes_BUILD_PAIR(N); break;
64     case ISD::ConstantFP:  R = SoftenFloatRes_ConstantFP(N); break;
65     case ISD::EXTRACT_VECTOR_ELT:
66       R = SoftenFloatRes_EXTRACT_VECTOR_ELT(N, ResNo); break;
67     case ISD::FABS:        R = SoftenFloatRes_FABS(N); break;
68     case ISD::STRICT_FMINNUM:
69     case ISD::FMINNUM:     R = SoftenFloatRes_FMINNUM(N); break;
70     case ISD::STRICT_FMAXNUM:
71     case ISD::FMAXNUM:     R = SoftenFloatRes_FMAXNUM(N); break;
72     case ISD::STRICT_FADD:
73     case ISD::FADD:        R = SoftenFloatRes_FADD(N); break;
74     case ISD::FCBRT:       R = SoftenFloatRes_FCBRT(N); break;
75     case ISD::STRICT_FCEIL:
76     case ISD::FCEIL:       R = SoftenFloatRes_FCEIL(N); break;
77     case ISD::FCOPYSIGN:   R = SoftenFloatRes_FCOPYSIGN(N); break;
78     case ISD::STRICT_FCOS:
79     case ISD::FCOS:        R = SoftenFloatRes_FCOS(N); break;
80     case ISD::STRICT_FDIV:
81     case ISD::FDIV:        R = SoftenFloatRes_FDIV(N); break;
82     case ISD::STRICT_FEXP:
83     case ISD::FEXP:        R = SoftenFloatRes_FEXP(N); break;
84     case ISD::STRICT_FEXP2:
85     case ISD::FEXP2:       R = SoftenFloatRes_FEXP2(N); break;
86     case ISD::STRICT_FFLOOR:
87     case ISD::FFLOOR:      R = SoftenFloatRes_FFLOOR(N); break;
88     case ISD::STRICT_FLOG:
89     case ISD::FLOG:        R = SoftenFloatRes_FLOG(N); break;
90     case ISD::STRICT_FLOG2:
91     case ISD::FLOG2:       R = SoftenFloatRes_FLOG2(N); break;
92     case ISD::STRICT_FLOG10:
93     case ISD::FLOG10:      R = SoftenFloatRes_FLOG10(N); break;
94     case ISD::STRICT_FMA:
95     case ISD::FMA:         R = SoftenFloatRes_FMA(N); break;
96     case ISD::STRICT_FMUL:
97     case ISD::FMUL:        R = SoftenFloatRes_FMUL(N); break;
98     case ISD::STRICT_FNEARBYINT:
99     case ISD::FNEARBYINT:  R = SoftenFloatRes_FNEARBYINT(N); break;
100     case ISD::FNEG:        R = SoftenFloatRes_FNEG(N); break;
101     case ISD::STRICT_FP_EXTEND:
102     case ISD::FP_EXTEND:   R = SoftenFloatRes_FP_EXTEND(N); break;
103     case ISD::STRICT_FP_ROUND:
104     case ISD::FP_ROUND:    R = SoftenFloatRes_FP_ROUND(N); break;
105     case ISD::FP16_TO_FP:  R = SoftenFloatRes_FP16_TO_FP(N); break;
106     case ISD::STRICT_FPOW:
107     case ISD::FPOW:        R = SoftenFloatRes_FPOW(N); break;
108     case ISD::STRICT_FPOWI:
109     case ISD::FPOWI:       R = SoftenFloatRes_FPOWI(N); break;
110     case ISD::STRICT_FREM:
111     case ISD::FREM:        R = SoftenFloatRes_FREM(N); break;
112     case ISD::STRICT_FRINT:
113     case ISD::FRINT:       R = SoftenFloatRes_FRINT(N); break;
114     case ISD::STRICT_FROUND:
115     case ISD::FROUND:      R = SoftenFloatRes_FROUND(N); break;
116     case ISD::STRICT_FSIN:
117     case ISD::FSIN:        R = SoftenFloatRes_FSIN(N); break;
118     case ISD::STRICT_FSQRT:
119     case ISD::FSQRT:       R = SoftenFloatRes_FSQRT(N); break;
120     case ISD::STRICT_FSUB:
121     case ISD::FSUB:        R = SoftenFloatRes_FSUB(N); break;
122     case ISD::STRICT_FTRUNC:
123     case ISD::FTRUNC:      R = SoftenFloatRes_FTRUNC(N); break;
124     case ISD::LOAD:        R = SoftenFloatRes_LOAD(N); break;
125     case ISD::ATOMIC_SWAP: R = BitcastToInt_ATOMIC_SWAP(N); break;
126     case ISD::SELECT:      R = SoftenFloatRes_SELECT(N); break;
127     case ISD::SELECT_CC:   R = SoftenFloatRes_SELECT_CC(N); break;
128     case ISD::STRICT_SINT_TO_FP:
129     case ISD::STRICT_UINT_TO_FP:
130     case ISD::SINT_TO_FP:
131     case ISD::UINT_TO_FP:  R = SoftenFloatRes_XINT_TO_FP(N); break;
132     case ISD::UNDEF:       R = SoftenFloatRes_UNDEF(N); break;
133     case ISD::VAARG:       R = SoftenFloatRes_VAARG(N); break;
134   }
135 
136   // If R is null, the sub-method took care of registering the result.
137   if (R.getNode()) {
138     assert(R.getNode() != N);
139     SetSoftenedFloat(SDValue(N, ResNo), R);
140   }
141 }
142 
143 SDValue DAGTypeLegalizer::SoftenFloatRes_Unary(SDNode *N, RTLIB::Libcall LC) {
144   bool IsStrict = N->isStrictFPOpcode();
145   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
146   unsigned Offset = IsStrict ? 1 : 0;
147   assert(N->getNumOperands() == (1 + Offset) &&
148          "Unexpected number of operands!");
149   SDValue Op = GetSoftenedFloat(N->getOperand(0 + Offset));
150   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
151   TargetLowering::MakeLibCallOptions CallOptions;
152   EVT OpVT = N->getOperand(0 + Offset).getValueType();
153   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
154   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
155                                                     CallOptions, SDLoc(N),
156                                                     Chain);
157   if (IsStrict)
158     ReplaceValueWith(SDValue(N, 1), Tmp.second);
159   return Tmp.first;
160 }
161 
162 SDValue DAGTypeLegalizer::SoftenFloatRes_Binary(SDNode *N, RTLIB::Libcall LC) {
163   bool IsStrict = N->isStrictFPOpcode();
164   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
165   unsigned Offset = IsStrict ? 1 : 0;
166   assert(N->getNumOperands() == (2 + Offset) &&
167          "Unexpected number of operands!");
168   SDValue Ops[2] = { GetSoftenedFloat(N->getOperand(0 + Offset)),
169                      GetSoftenedFloat(N->getOperand(1 + Offset)) };
170   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
171   TargetLowering::MakeLibCallOptions CallOptions;
172   EVT OpsVT[2] = { N->getOperand(0 + Offset).getValueType(),
173                    N->getOperand(1 + Offset).getValueType() };
174   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
175   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Ops,
176                                                     CallOptions, SDLoc(N),
177                                                     Chain);
178   if (IsStrict)
179     ReplaceValueWith(SDValue(N, 1), Tmp.second);
180   return Tmp.first;
181 }
182 
183 SDValue DAGTypeLegalizer::SoftenFloatRes_BITCAST(SDNode *N) {
184   return BitConvertToInteger(N->getOperand(0));
185 }
186 
187 SDValue DAGTypeLegalizer::SoftenFloatRes_MERGE_VALUES(SDNode *N,
188                                                       unsigned ResNo) {
189   SDValue Op = DisintegrateMERGE_VALUES(N, ResNo);
190   return BitConvertToInteger(Op);
191 }
192 
193 SDValue DAGTypeLegalizer::SoftenFloatRes_BUILD_PAIR(SDNode *N) {
194   // Convert the inputs to integers, and build a new pair out of them.
195   return DAG.getNode(ISD::BUILD_PAIR, SDLoc(N),
196                      TLI.getTypeToTransformTo(*DAG.getContext(),
197                                               N->getValueType(0)),
198                      BitConvertToInteger(N->getOperand(0)),
199                      BitConvertToInteger(N->getOperand(1)));
200 }
201 
202 SDValue DAGTypeLegalizer::SoftenFloatRes_ConstantFP(SDNode *N) {
203   ConstantFPSDNode *CN = cast<ConstantFPSDNode>(N);
204   // In ppcf128, the high 64 bits are always first in memory regardless
205   // of Endianness. LLVM's APFloat representation is not Endian sensitive,
206   // and so always converts into a 128-bit APInt in a non-Endian-sensitive
207   // way. However, APInt's are serialized in an Endian-sensitive fashion,
208   // so on big-Endian targets, the two doubles are output in the wrong
209   // order. Fix this by manually flipping the order of the high 64 bits
210   // and the low 64 bits here.
211   if (DAG.getDataLayout().isBigEndian() &&
212       CN->getValueType(0).getSimpleVT() == llvm::MVT::ppcf128) {
213     uint64_t words[2] = { CN->getValueAPF().bitcastToAPInt().getRawData()[1],
214                           CN->getValueAPF().bitcastToAPInt().getRawData()[0] };
215     APInt Val(128, words);
216     return DAG.getConstant(Val, SDLoc(CN),
217                            TLI.getTypeToTransformTo(*DAG.getContext(),
218                                                     CN->getValueType(0)));
219   } else {
220     return DAG.getConstant(CN->getValueAPF().bitcastToAPInt(), SDLoc(CN),
221                            TLI.getTypeToTransformTo(*DAG.getContext(),
222                                                     CN->getValueType(0)));
223   }
224 }
225 
226 SDValue DAGTypeLegalizer::SoftenFloatRes_EXTRACT_VECTOR_ELT(SDNode *N, unsigned ResNo) {
227   SDValue NewOp = BitConvertVectorToIntegerVector(N->getOperand(0));
228   return DAG.getNode(ISD::EXTRACT_VECTOR_ELT, SDLoc(N),
229                      NewOp.getValueType().getVectorElementType(),
230                      NewOp, N->getOperand(1));
231 }
232 
233 SDValue DAGTypeLegalizer::SoftenFloatRes_FABS(SDNode *N) {
234   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
235   unsigned Size = NVT.getSizeInBits();
236 
237   // Mask = ~(1 << (Size-1))
238   APInt API = APInt::getAllOnesValue(Size);
239   API.clearBit(Size - 1);
240   SDValue Mask = DAG.getConstant(API, SDLoc(N), NVT);
241   SDValue Op = GetSoftenedFloat(N->getOperand(0));
242   return DAG.getNode(ISD::AND, SDLoc(N), NVT, Op, Mask);
243 }
244 
245 SDValue DAGTypeLegalizer::SoftenFloatRes_FMINNUM(SDNode *N) {
246   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
247                                                RTLIB::FMIN_F32,
248                                                RTLIB::FMIN_F64,
249                                                RTLIB::FMIN_F80,
250                                                RTLIB::FMIN_F128,
251                                                RTLIB::FMIN_PPCF128));
252 }
253 
254 SDValue DAGTypeLegalizer::SoftenFloatRes_FMAXNUM(SDNode *N) {
255   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
256                                                RTLIB::FMAX_F32,
257                                                RTLIB::FMAX_F64,
258                                                RTLIB::FMAX_F80,
259                                                RTLIB::FMAX_F128,
260                                                RTLIB::FMAX_PPCF128));
261 }
262 
263 SDValue DAGTypeLegalizer::SoftenFloatRes_FADD(SDNode *N) {
264   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
265                                                RTLIB::ADD_F32,
266                                                RTLIB::ADD_F64,
267                                                RTLIB::ADD_F80,
268                                                RTLIB::ADD_F128,
269                                                RTLIB::ADD_PPCF128));
270 }
271 
272 SDValue DAGTypeLegalizer::SoftenFloatRes_FCBRT(SDNode *N) {
273   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
274                                            RTLIB::CBRT_F32,
275                                            RTLIB::CBRT_F64,
276                                            RTLIB::CBRT_F80,
277                                            RTLIB::CBRT_F128,
278                                            RTLIB::CBRT_PPCF128));
279 }
280 
281 SDValue DAGTypeLegalizer::SoftenFloatRes_FCEIL(SDNode *N) {
282   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
283                                               RTLIB::CEIL_F32,
284                                               RTLIB::CEIL_F64,
285                                               RTLIB::CEIL_F80,
286                                               RTLIB::CEIL_F128,
287                                               RTLIB::CEIL_PPCF128));
288 }
289 
290 SDValue DAGTypeLegalizer::SoftenFloatRes_FCOPYSIGN(SDNode *N) {
291   SDValue LHS = GetSoftenedFloat(N->getOperand(0));
292   SDValue RHS = BitConvertToInteger(N->getOperand(1));
293   SDLoc dl(N);
294 
295   EVT LVT = LHS.getValueType();
296   EVT RVT = RHS.getValueType();
297 
298   unsigned LSize = LVT.getSizeInBits();
299   unsigned RSize = RVT.getSizeInBits();
300 
301   // First get the sign bit of second operand.
302   SDValue SignBit = DAG.getNode(
303       ISD::SHL, dl, RVT, DAG.getConstant(1, dl, RVT),
304       DAG.getConstant(RSize - 1, dl,
305                       TLI.getShiftAmountTy(RVT, DAG.getDataLayout())));
306   SignBit = DAG.getNode(ISD::AND, dl, RVT, RHS, SignBit);
307 
308   // Shift right or sign-extend it if the two operands have different types.
309   int SizeDiff = RVT.getSizeInBits() - LVT.getSizeInBits();
310   if (SizeDiff > 0) {
311     SignBit =
312         DAG.getNode(ISD::SRL, dl, RVT, SignBit,
313                     DAG.getConstant(SizeDiff, dl,
314                                     TLI.getShiftAmountTy(SignBit.getValueType(),
315                                                          DAG.getDataLayout())));
316     SignBit = DAG.getNode(ISD::TRUNCATE, dl, LVT, SignBit);
317   } else if (SizeDiff < 0) {
318     SignBit = DAG.getNode(ISD::ANY_EXTEND, dl, LVT, SignBit);
319     SignBit =
320         DAG.getNode(ISD::SHL, dl, LVT, SignBit,
321                     DAG.getConstant(-SizeDiff, dl,
322                                     TLI.getShiftAmountTy(SignBit.getValueType(),
323                                                          DAG.getDataLayout())));
324   }
325 
326   // Clear the sign bit of the first operand.
327   SDValue Mask = DAG.getNode(
328       ISD::SHL, dl, LVT, DAG.getConstant(1, dl, LVT),
329       DAG.getConstant(LSize - 1, dl,
330                       TLI.getShiftAmountTy(LVT, DAG.getDataLayout())));
331   Mask = DAG.getNode(ISD::SUB, dl, LVT, Mask, DAG.getConstant(1, dl, LVT));
332   LHS = DAG.getNode(ISD::AND, dl, LVT, LHS, Mask);
333 
334   // Or the value with the sign bit.
335   return DAG.getNode(ISD::OR, dl, LVT, LHS, SignBit);
336 }
337 
338 SDValue DAGTypeLegalizer::SoftenFloatRes_FCOS(SDNode *N) {
339   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
340                                               RTLIB::COS_F32,
341                                               RTLIB::COS_F64,
342                                               RTLIB::COS_F80,
343                                               RTLIB::COS_F128,
344                                               RTLIB::COS_PPCF128));
345 }
346 
347 SDValue DAGTypeLegalizer::SoftenFloatRes_FDIV(SDNode *N) {
348   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
349                                                RTLIB::DIV_F32,
350                                                RTLIB::DIV_F64,
351                                                RTLIB::DIV_F80,
352                                                RTLIB::DIV_F128,
353                                                RTLIB::DIV_PPCF128));
354 }
355 
356 SDValue DAGTypeLegalizer::SoftenFloatRes_FEXP(SDNode *N) {
357   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
358                                               RTLIB::EXP_F32,
359                                               RTLIB::EXP_F64,
360                                               RTLIB::EXP_F80,
361                                               RTLIB::EXP_F128,
362                                               RTLIB::EXP_PPCF128));
363 }
364 
365 SDValue DAGTypeLegalizer::SoftenFloatRes_FEXP2(SDNode *N) {
366   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
367                                               RTLIB::EXP2_F32,
368                                               RTLIB::EXP2_F64,
369                                               RTLIB::EXP2_F80,
370                                               RTLIB::EXP2_F128,
371                                               RTLIB::EXP2_PPCF128));
372 }
373 
374 SDValue DAGTypeLegalizer::SoftenFloatRes_FFLOOR(SDNode *N) {
375   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
376                                               RTLIB::FLOOR_F32,
377                                               RTLIB::FLOOR_F64,
378                                               RTLIB::FLOOR_F80,
379                                               RTLIB::FLOOR_F128,
380                                               RTLIB::FLOOR_PPCF128));
381 }
382 
383 SDValue DAGTypeLegalizer::SoftenFloatRes_FLOG(SDNode *N) {
384   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
385                                               RTLIB::LOG_F32,
386                                               RTLIB::LOG_F64,
387                                               RTLIB::LOG_F80,
388                                               RTLIB::LOG_F128,
389                                               RTLIB::LOG_PPCF128));
390 }
391 
392 SDValue DAGTypeLegalizer::SoftenFloatRes_FLOG2(SDNode *N) {
393   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
394                                               RTLIB::LOG2_F32,
395                                               RTLIB::LOG2_F64,
396                                               RTLIB::LOG2_F80,
397                                               RTLIB::LOG2_F128,
398                                               RTLIB::LOG2_PPCF128));
399 }
400 
401 SDValue DAGTypeLegalizer::SoftenFloatRes_FLOG10(SDNode *N) {
402   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
403                                               RTLIB::LOG10_F32,
404                                               RTLIB::LOG10_F64,
405                                               RTLIB::LOG10_F80,
406                                               RTLIB::LOG10_F128,
407                                               RTLIB::LOG10_PPCF128));
408 }
409 
410 SDValue DAGTypeLegalizer::SoftenFloatRes_FMA(SDNode *N) {
411   bool IsStrict = N->isStrictFPOpcode();
412   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
413   unsigned Offset = IsStrict ? 1 : 0;
414   SDValue Ops[3] = { GetSoftenedFloat(N->getOperand(0 + Offset)),
415                      GetSoftenedFloat(N->getOperand(1 + Offset)),
416                      GetSoftenedFloat(N->getOperand(2 + Offset)) };
417   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
418   TargetLowering::MakeLibCallOptions CallOptions;
419   EVT OpsVT[3] = { N->getOperand(0 + Offset).getValueType(),
420                    N->getOperand(1 + Offset).getValueType(),
421                    N->getOperand(2 + Offset).getValueType() };
422   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
423   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG,
424                                                     GetFPLibCall(N->getValueType(0),
425                                                                  RTLIB::FMA_F32,
426                                                                  RTLIB::FMA_F64,
427                                                                  RTLIB::FMA_F80,
428                                                                  RTLIB::FMA_F128,
429                                                                  RTLIB::FMA_PPCF128),
430                          NVT, Ops, CallOptions, SDLoc(N), Chain);
431   if (IsStrict)
432     ReplaceValueWith(SDValue(N, 1), Tmp.second);
433   return Tmp.first;
434 }
435 
436 SDValue DAGTypeLegalizer::SoftenFloatRes_FMUL(SDNode *N) {
437   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
438                                                RTLIB::MUL_F32,
439                                                RTLIB::MUL_F64,
440                                                RTLIB::MUL_F80,
441                                                RTLIB::MUL_F128,
442                                                RTLIB::MUL_PPCF128));
443 }
444 
445 SDValue DAGTypeLegalizer::SoftenFloatRes_FNEARBYINT(SDNode *N) {
446   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
447                                               RTLIB::NEARBYINT_F32,
448                                               RTLIB::NEARBYINT_F64,
449                                               RTLIB::NEARBYINT_F80,
450                                               RTLIB::NEARBYINT_F128,
451                                               RTLIB::NEARBYINT_PPCF128));
452 }
453 
454 SDValue DAGTypeLegalizer::SoftenFloatRes_FNEG(SDNode *N) {
455   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
456   SDLoc dl(N);
457 
458   // Expand Y = FNEG(X) -> Y = X ^ sign mask
459   APInt SignMask = APInt::getSignMask(NVT.getSizeInBits());
460   return DAG.getNode(ISD::XOR, dl, NVT, GetSoftenedFloat(N->getOperand(0)),
461                      DAG.getConstant(SignMask, dl, NVT));
462 }
463 
464 SDValue DAGTypeLegalizer::SoftenFloatRes_FP_EXTEND(SDNode *N) {
465   bool IsStrict = N->isStrictFPOpcode();
466   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
467   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
468 
469   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
470 
471   if (getTypeAction(Op.getValueType()) == TargetLowering::TypePromoteFloat) {
472     Op = GetPromotedFloat(Op);
473     // If the promotion did the FP_EXTEND to the destination type for us,
474     // there's nothing left to do here.
475     if (Op.getValueType() == N->getValueType(0))
476       return BitConvertToInteger(Op);
477   }
478 
479   // There's only a libcall for f16 -> f32, so proceed in two stages. Also, it's
480   // entirely possible for both f16 and f32 to be legal, so use the fully
481   // hard-float FP_EXTEND rather than FP16_TO_FP.
482   if (Op.getValueType() == MVT::f16 && N->getValueType(0) != MVT::f32) {
483     if (IsStrict) {
484       Op = DAG.getNode(ISD::STRICT_FP_EXTEND, SDLoc(N),
485                        { MVT::f32, MVT::Other }, { Chain, Op });
486       Chain = Op.getValue(1);
487     } else {
488       Op = DAG.getNode(ISD::FP_EXTEND, SDLoc(N), MVT::f32, Op);
489     }
490   }
491 
492   RTLIB::Libcall LC = RTLIB::getFPEXT(Op.getValueType(), N->getValueType(0));
493   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_EXTEND!");
494   TargetLowering::MakeLibCallOptions CallOptions;
495   EVT OpVT = N->getOperand(IsStrict ? 1 : 0).getValueType();
496   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
497   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
498                                                     CallOptions, SDLoc(N),
499                                                     Chain);
500   if (IsStrict)
501     ReplaceValueWith(SDValue(N, 1), Tmp.second);
502   return Tmp.first;
503 }
504 
505 // FIXME: Should we just use 'normal' FP_EXTEND / FP_TRUNC instead of special
506 // nodes?
507 SDValue DAGTypeLegalizer::SoftenFloatRes_FP16_TO_FP(SDNode *N) {
508   EVT MidVT = TLI.getTypeToTransformTo(*DAG.getContext(), MVT::f32);
509   SDValue Op = N->getOperand(0);
510   TargetLowering::MakeLibCallOptions CallOptions;
511   EVT OpsVT[1] = { N->getOperand(0).getValueType() };
512   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
513   SDValue Res32 = TLI.makeLibCall(DAG, RTLIB::FPEXT_F16_F32, MidVT, Op,
514                                   CallOptions, SDLoc(N)).first;
515   if (N->getValueType(0) == MVT::f32)
516     return Res32;
517 
518   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
519   RTLIB::Libcall LC = RTLIB::getFPEXT(MVT::f32, N->getValueType(0));
520   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_EXTEND!");
521   return TLI.makeLibCall(DAG, LC, NVT, Res32, CallOptions, SDLoc(N)).first;
522 }
523 
524 SDValue DAGTypeLegalizer::SoftenFloatRes_FP_ROUND(SDNode *N) {
525   bool IsStrict = N->isStrictFPOpcode();
526   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
527   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
528   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
529   RTLIB::Libcall LC = RTLIB::getFPROUND(Op.getValueType(), N->getValueType(0));
530   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_ROUND!");
531   TargetLowering::MakeLibCallOptions CallOptions;
532   EVT OpVT = N->getOperand(IsStrict ? 1 : 0).getValueType();
533   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
534   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
535                                                     CallOptions, SDLoc(N),
536                                                     Chain);
537   if (IsStrict)
538     ReplaceValueWith(SDValue(N, 1), Tmp.second);
539   return Tmp.first;
540 }
541 
542 SDValue DAGTypeLegalizer::SoftenFloatRes_FPOW(SDNode *N) {
543   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
544                                                RTLIB::POW_F32,
545                                                RTLIB::POW_F64,
546                                                RTLIB::POW_F80,
547                                                RTLIB::POW_F128,
548                                                RTLIB::POW_PPCF128));
549 }
550 
551 SDValue DAGTypeLegalizer::SoftenFloatRes_FPOWI(SDNode *N) {
552   bool IsStrict = N->isStrictFPOpcode();
553   unsigned Offset = IsStrict ? 1 : 0;
554   assert(N->getOperand(1 + Offset).getValueType() == MVT::i32 &&
555          "Unsupported power type!");
556   RTLIB::Libcall LC = GetFPLibCall(N->getValueType(0),
557                                    RTLIB::POWI_F32,
558                                    RTLIB::POWI_F64,
559                                    RTLIB::POWI_F80,
560                                    RTLIB::POWI_F128,
561                                    RTLIB::POWI_PPCF128);
562   if (!TLI.getLibcallName(LC)) {
563     // Some targets don't have a powi libcall; use pow instead.
564     // FIXME: Implement this if some target needs it.
565     DAG.getContext()->emitError("Don't know how to soften fpowi to fpow");
566     return DAG.getUNDEF(N->getValueType(0));
567   }
568 
569   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
570   SDValue Ops[2] = { GetSoftenedFloat(N->getOperand(0 + Offset)),
571                      N->getOperand(1 + Offset) };
572   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
573   TargetLowering::MakeLibCallOptions CallOptions;
574   EVT OpsVT[2] = { N->getOperand(0 + Offset).getValueType(),
575                    N->getOperand(1 + Offset).getValueType() };
576   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
577   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Ops,
578                                                     CallOptions, SDLoc(N),
579                                                     Chain);
580   if (IsStrict)
581     ReplaceValueWith(SDValue(N, 1), Tmp.second);
582   return Tmp.first;
583 }
584 
585 SDValue DAGTypeLegalizer::SoftenFloatRes_FREM(SDNode *N) {
586   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
587                                                RTLIB::REM_F32,
588                                                RTLIB::REM_F64,
589                                                RTLIB::REM_F80,
590                                                RTLIB::REM_F128,
591                                                RTLIB::REM_PPCF128));
592 }
593 
594 SDValue DAGTypeLegalizer::SoftenFloatRes_FRINT(SDNode *N) {
595   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
596                                               RTLIB::RINT_F32,
597                                               RTLIB::RINT_F64,
598                                               RTLIB::RINT_F80,
599                                               RTLIB::RINT_F128,
600                                               RTLIB::RINT_PPCF128));
601 }
602 
603 SDValue DAGTypeLegalizer::SoftenFloatRes_FROUND(SDNode *N) {
604   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
605                                               RTLIB::ROUND_F32,
606                                               RTLIB::ROUND_F64,
607                                               RTLIB::ROUND_F80,
608                                               RTLIB::ROUND_F128,
609                                               RTLIB::ROUND_PPCF128));
610 }
611 
612 SDValue DAGTypeLegalizer::SoftenFloatRes_FSIN(SDNode *N) {
613   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
614                                               RTLIB::SIN_F32,
615                                               RTLIB::SIN_F64,
616                                               RTLIB::SIN_F80,
617                                               RTLIB::SIN_F128,
618                                               RTLIB::SIN_PPCF128));
619 }
620 
621 SDValue DAGTypeLegalizer::SoftenFloatRes_FSQRT(SDNode *N) {
622   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
623                                               RTLIB::SQRT_F32,
624                                               RTLIB::SQRT_F64,
625                                               RTLIB::SQRT_F80,
626                                               RTLIB::SQRT_F128,
627                                               RTLIB::SQRT_PPCF128));
628 }
629 
630 SDValue DAGTypeLegalizer::SoftenFloatRes_FSUB(SDNode *N) {
631   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
632                                                RTLIB::SUB_F32,
633                                                RTLIB::SUB_F64,
634                                                RTLIB::SUB_F80,
635                                                RTLIB::SUB_F128,
636                                                RTLIB::SUB_PPCF128));
637 }
638 
639 SDValue DAGTypeLegalizer::SoftenFloatRes_FTRUNC(SDNode *N) {
640   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
641                                               RTLIB::TRUNC_F32,
642                                               RTLIB::TRUNC_F64,
643                                               RTLIB::TRUNC_F80,
644                                               RTLIB::TRUNC_F128,
645                                               RTLIB::TRUNC_PPCF128));
646 }
647 
648 SDValue DAGTypeLegalizer::SoftenFloatRes_LOAD(SDNode *N) {
649   LoadSDNode *L = cast<LoadSDNode>(N);
650   EVT VT = N->getValueType(0);
651   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
652   SDLoc dl(N);
653 
654   auto MMOFlags =
655       L->getMemOperand()->getFlags() &
656       ~(MachineMemOperand::MOInvariant | MachineMemOperand::MODereferenceable);
657   SDValue NewL;
658   if (L->getExtensionType() == ISD::NON_EXTLOAD) {
659     NewL = DAG.getLoad(L->getAddressingMode(), L->getExtensionType(), NVT, dl,
660                        L->getChain(), L->getBasePtr(), L->getOffset(),
661                        L->getPointerInfo(), NVT, L->getAlignment(), MMOFlags,
662                        L->getAAInfo());
663     // Legalized the chain result - switch anything that used the old chain to
664     // use the new one.
665     ReplaceValueWith(SDValue(N, 1), NewL.getValue(1));
666     return NewL;
667   }
668 
669   // Do a non-extending load followed by FP_EXTEND.
670   NewL = DAG.getLoad(L->getAddressingMode(), ISD::NON_EXTLOAD, L->getMemoryVT(),
671                      dl, L->getChain(), L->getBasePtr(), L->getOffset(),
672                      L->getPointerInfo(), L->getMemoryVT(), L->getAlignment(),
673                      MMOFlags, L->getAAInfo());
674   // Legalized the chain result - switch anything that used the old chain to
675   // use the new one.
676   ReplaceValueWith(SDValue(N, 1), NewL.getValue(1));
677   auto ExtendNode = DAG.getNode(ISD::FP_EXTEND, dl, VT, NewL);
678   return BitConvertToInteger(ExtendNode);
679 }
680 
681 SDValue DAGTypeLegalizer::SoftenFloatRes_SELECT(SDNode *N) {
682   SDValue LHS = GetSoftenedFloat(N->getOperand(1));
683   SDValue RHS = GetSoftenedFloat(N->getOperand(2));
684   return DAG.getSelect(SDLoc(N),
685                        LHS.getValueType(), N->getOperand(0), LHS, RHS);
686 }
687 
688 SDValue DAGTypeLegalizer::SoftenFloatRes_SELECT_CC(SDNode *N) {
689   SDValue LHS = GetSoftenedFloat(N->getOperand(2));
690   SDValue RHS = GetSoftenedFloat(N->getOperand(3));
691   return DAG.getNode(ISD::SELECT_CC, SDLoc(N),
692                      LHS.getValueType(), N->getOperand(0),
693                      N->getOperand(1), LHS, RHS, N->getOperand(4));
694 }
695 
696 SDValue DAGTypeLegalizer::SoftenFloatRes_UNDEF(SDNode *N) {
697   return DAG.getUNDEF(TLI.getTypeToTransformTo(*DAG.getContext(),
698                                                N->getValueType(0)));
699 }
700 
701 SDValue DAGTypeLegalizer::SoftenFloatRes_VAARG(SDNode *N) {
702   SDValue Chain = N->getOperand(0); // Get the chain.
703   SDValue Ptr = N->getOperand(1); // Get the pointer.
704   EVT VT = N->getValueType(0);
705   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
706   SDLoc dl(N);
707 
708   SDValue NewVAARG;
709   NewVAARG = DAG.getVAArg(NVT, dl, Chain, Ptr, N->getOperand(2),
710                           N->getConstantOperandVal(3));
711 
712   // Legalized the chain result - switch anything that used the old chain to
713   // use the new one.
714   if (N != NewVAARG.getValue(1).getNode())
715     ReplaceValueWith(SDValue(N, 1), NewVAARG.getValue(1));
716   return NewVAARG;
717 }
718 
719 SDValue DAGTypeLegalizer::SoftenFloatRes_XINT_TO_FP(SDNode *N) {
720   bool IsStrict = N->isStrictFPOpcode();
721   bool Signed = N->getOpcode() == ISD::SINT_TO_FP ||
722                 N->getOpcode() == ISD::STRICT_SINT_TO_FP;
723   EVT SVT = N->getOperand(IsStrict ? 1 : 0).getValueType();
724   EVT RVT = N->getValueType(0);
725   EVT NVT = EVT();
726   SDLoc dl(N);
727 
728   // If the input is not legal, eg: i1 -> fp, then it needs to be promoted to
729   // a larger type, eg: i8 -> fp.  Even if it is legal, no libcall may exactly
730   // match.  Look for an appropriate libcall.
731   RTLIB::Libcall LC = RTLIB::UNKNOWN_LIBCALL;
732   for (unsigned t = MVT::FIRST_INTEGER_VALUETYPE;
733        t <= MVT::LAST_INTEGER_VALUETYPE && LC == RTLIB::UNKNOWN_LIBCALL; ++t) {
734     NVT = (MVT::SimpleValueType)t;
735     // The source needs to big enough to hold the operand.
736     if (NVT.bitsGE(SVT))
737       LC = Signed ? RTLIB::getSINTTOFP(NVT, RVT):RTLIB::getUINTTOFP (NVT, RVT);
738   }
739   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported XINT_TO_FP!");
740 
741   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
742   // Sign/zero extend the argument if the libcall takes a larger type.
743   SDValue Op = DAG.getNode(Signed ? ISD::SIGN_EXTEND : ISD::ZERO_EXTEND, dl,
744                            NVT, N->getOperand(IsStrict ? 1 : 0));
745   TargetLowering::MakeLibCallOptions CallOptions;
746   CallOptions.setSExt(Signed);
747   CallOptions.setTypeListBeforeSoften(SVT, RVT, true);
748   std::pair<SDValue, SDValue> Tmp =
749       TLI.makeLibCall(DAG, LC, TLI.getTypeToTransformTo(*DAG.getContext(), RVT),
750                       Op, CallOptions, dl, Chain);
751 
752   if (IsStrict)
753     ReplaceValueWith(SDValue(N, 1), Tmp.second);
754   return Tmp.first;
755 }
756 
757 
758 //===----------------------------------------------------------------------===//
759 //  Convert Float Operand to Integer
760 //===----------------------------------------------------------------------===//
761 
762 bool DAGTypeLegalizer::SoftenFloatOperand(SDNode *N, unsigned OpNo) {
763   LLVM_DEBUG(dbgs() << "Soften float operand " << OpNo << ": "; N->dump(&DAG);
764              dbgs() << "\n");
765   SDValue Res = SDValue();
766 
767   switch (N->getOpcode()) {
768   default:
769 #ifndef NDEBUG
770     dbgs() << "SoftenFloatOperand Op #" << OpNo << ": ";
771     N->dump(&DAG); dbgs() << "\n";
772 #endif
773     llvm_unreachable("Do not know how to soften this operator's operand!");
774 
775   case ISD::BITCAST:     Res = SoftenFloatOp_BITCAST(N); break;
776   case ISD::BR_CC:       Res = SoftenFloatOp_BR_CC(N); break;
777   case ISD::FP_TO_FP16:  // Same as FP_ROUND for softening purposes
778   case ISD::STRICT_FP_ROUND:
779   case ISD::FP_ROUND:    Res = SoftenFloatOp_FP_ROUND(N); break;
780   case ISD::STRICT_FP_TO_SINT:
781   case ISD::STRICT_FP_TO_UINT:
782   case ISD::FP_TO_SINT:
783   case ISD::FP_TO_UINT:  Res = SoftenFloatOp_FP_TO_XINT(N); break;
784   case ISD::STRICT_LROUND:
785   case ISD::LROUND:      Res = SoftenFloatOp_LROUND(N); break;
786   case ISD::STRICT_LLROUND:
787   case ISD::LLROUND:     Res = SoftenFloatOp_LLROUND(N); break;
788   case ISD::STRICT_LRINT:
789   case ISD::LRINT:       Res = SoftenFloatOp_LRINT(N); break;
790   case ISD::STRICT_LLRINT:
791   case ISD::LLRINT:      Res = SoftenFloatOp_LLRINT(N); break;
792   case ISD::SELECT_CC:   Res = SoftenFloatOp_SELECT_CC(N); break;
793   case ISD::STRICT_FSETCC:
794   case ISD::STRICT_FSETCCS:
795   case ISD::SETCC:       Res = SoftenFloatOp_SETCC(N); break;
796   case ISD::STORE:       Res = SoftenFloatOp_STORE(N, OpNo); break;
797   case ISD::FCOPYSIGN:   Res = SoftenFloatOp_FCOPYSIGN(N); break;
798   }
799 
800   // If the result is null, the sub-method took care of registering results etc.
801   if (!Res.getNode()) return false;
802 
803   // If the result is N, the sub-method updated N in place.  Tell the legalizer
804   // core about this to re-analyze.
805   if (Res.getNode() == N)
806     return true;
807 
808   assert(Res.getValueType() == N->getValueType(0) && N->getNumValues() == 1 &&
809          "Invalid operand softening");
810 
811   ReplaceValueWith(SDValue(N, 0), Res);
812   return false;
813 }
814 
815 SDValue DAGTypeLegalizer::SoftenFloatOp_BITCAST(SDNode *N) {
816   SDValue Op0 = GetSoftenedFloat(N->getOperand(0));
817 
818   return DAG.getNode(ISD::BITCAST, SDLoc(N), N->getValueType(0), Op0);
819 }
820 
821 SDValue DAGTypeLegalizer::SoftenFloatOp_FP_ROUND(SDNode *N) {
822   // We actually deal with the partially-softened FP_TO_FP16 node too, which
823   // returns an i16 so doesn't meet the constraints necessary for FP_ROUND.
824   assert(N->getOpcode() == ISD::FP_ROUND || N->getOpcode() == ISD::FP_TO_FP16 ||
825          N->getOpcode() == ISD::STRICT_FP_ROUND);
826 
827   bool IsStrict = N->isStrictFPOpcode();
828   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
829   EVT SVT = Op.getValueType();
830   EVT RVT = N->getValueType(0);
831   EVT FloatRVT = N->getOpcode() == ISD::FP_TO_FP16 ? MVT::f16 : RVT;
832 
833   RTLIB::Libcall LC = RTLIB::getFPROUND(SVT, FloatRVT);
834   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_ROUND libcall");
835 
836   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
837   Op = GetSoftenedFloat(Op);
838   TargetLowering::MakeLibCallOptions CallOptions;
839   CallOptions.setTypeListBeforeSoften(SVT, RVT, true);
840   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, RVT, Op,
841                                                     CallOptions, SDLoc(N),
842                                                     Chain);
843   if (IsStrict) {
844     ReplaceValueWith(SDValue(N, 1), Tmp.second);
845     ReplaceValueWith(SDValue(N, 0), Tmp.first);
846     return SDValue();
847   }
848   return Tmp.first;
849 }
850 
851 SDValue DAGTypeLegalizer::SoftenFloatOp_BR_CC(SDNode *N) {
852   SDValue NewLHS = N->getOperand(2), NewRHS = N->getOperand(3);
853   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(1))->get();
854 
855   EVT VT = NewLHS.getValueType();
856   NewLHS = GetSoftenedFloat(NewLHS);
857   NewRHS = GetSoftenedFloat(NewRHS);
858   TLI.softenSetCCOperands(DAG, VT, NewLHS, NewRHS, CCCode, SDLoc(N),
859                           N->getOperand(2), N->getOperand(3));
860 
861   // If softenSetCCOperands returned a scalar, we need to compare the result
862   // against zero to select between true and false values.
863   if (!NewRHS.getNode()) {
864     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
865     CCCode = ISD::SETNE;
866   }
867 
868   // Update N to have the operands specified.
869   return SDValue(DAG.UpdateNodeOperands(N, N->getOperand(0),
870                                 DAG.getCondCode(CCCode), NewLHS, NewRHS,
871                                 N->getOperand(4)),
872                  0);
873 }
874 
875 SDValue DAGTypeLegalizer::SoftenFloatOp_FP_TO_XINT(SDNode *N) {
876   bool IsStrict = N->isStrictFPOpcode();
877   bool Signed = N->getOpcode() == ISD::FP_TO_SINT ||
878                 N->getOpcode() == ISD::STRICT_FP_TO_SINT;
879 
880   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
881   EVT SVT = Op.getValueType();
882   EVT RVT = N->getValueType(0);
883   EVT NVT = EVT();
884   SDLoc dl(N);
885 
886   // If the result is not legal, eg: fp -> i1, then it needs to be promoted to
887   // a larger type, eg: fp -> i32. Even if it is legal, no libcall may exactly
888   // match, eg. we don't have fp -> i8 conversions.
889   // Look for an appropriate libcall.
890   RTLIB::Libcall LC = RTLIB::UNKNOWN_LIBCALL;
891   for (unsigned IntVT = MVT::FIRST_INTEGER_VALUETYPE;
892        IntVT <= MVT::LAST_INTEGER_VALUETYPE && LC == RTLIB::UNKNOWN_LIBCALL;
893        ++IntVT) {
894     NVT = (MVT::SimpleValueType)IntVT;
895     // The type needs to big enough to hold the result.
896     if (NVT.bitsGE(RVT))
897       LC = Signed ? RTLIB::getFPTOSINT(SVT, NVT) : RTLIB::getFPTOUINT(SVT, NVT);
898   }
899   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_TO_XINT!");
900 
901   Op = GetSoftenedFloat(Op);
902   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
903   TargetLowering::MakeLibCallOptions CallOptions;
904   CallOptions.setTypeListBeforeSoften(SVT, RVT, true);
905   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
906                                                     CallOptions, dl, Chain);
907 
908   // Truncate the result if the libcall returns a larger type.
909   SDValue Res = DAG.getNode(ISD::TRUNCATE, dl, RVT, Tmp.first);
910 
911   if (!IsStrict)
912     return Res;
913 
914   ReplaceValueWith(SDValue(N, 1), Tmp.second);
915   ReplaceValueWith(SDValue(N, 0), Res);
916   return SDValue();
917 }
918 
919 SDValue DAGTypeLegalizer::SoftenFloatOp_SELECT_CC(SDNode *N) {
920   SDValue NewLHS = N->getOperand(0), NewRHS = N->getOperand(1);
921   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(4))->get();
922 
923   EVT VT = NewLHS.getValueType();
924   NewLHS = GetSoftenedFloat(NewLHS);
925   NewRHS = GetSoftenedFloat(NewRHS);
926   TLI.softenSetCCOperands(DAG, VT, NewLHS, NewRHS, CCCode, SDLoc(N),
927                           N->getOperand(0), N->getOperand(1));
928 
929   // If softenSetCCOperands returned a scalar, we need to compare the result
930   // against zero to select between true and false values.
931   if (!NewRHS.getNode()) {
932     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
933     CCCode = ISD::SETNE;
934   }
935 
936   // Update N to have the operands specified.
937   return SDValue(DAG.UpdateNodeOperands(N, NewLHS, NewRHS,
938                                 N->getOperand(2), N->getOperand(3),
939                                 DAG.getCondCode(CCCode)),
940                  0);
941 }
942 
943 SDValue DAGTypeLegalizer::SoftenFloatOp_SETCC(SDNode *N) {
944   bool IsStrict = N->isStrictFPOpcode();
945   SDValue Op0 = N->getOperand(IsStrict ? 1 : 0);
946   SDValue Op1 = N->getOperand(IsStrict ? 2 : 1);
947   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
948   ISD::CondCode CCCode =
949       cast<CondCodeSDNode>(N->getOperand(IsStrict ? 3 : 2))->get();
950 
951   EVT VT = Op0.getValueType();
952   SDValue NewLHS = GetSoftenedFloat(Op0);
953   SDValue NewRHS = GetSoftenedFloat(Op1);
954   TLI.softenSetCCOperands(DAG, VT, NewLHS, NewRHS, CCCode, SDLoc(N), Op0, Op1,
955                           Chain, N->getOpcode() == ISD::STRICT_FSETCCS);
956 
957   // Update N to have the operands specified.
958   if (NewRHS.getNode()) {
959     if (IsStrict)
960       NewLHS = DAG.getNode(ISD::SETCC, SDLoc(N), N->getValueType(0), NewLHS,
961                            NewRHS, DAG.getCondCode(CCCode));
962     else
963       return SDValue(DAG.UpdateNodeOperands(N, NewLHS, NewRHS,
964                                             DAG.getCondCode(CCCode)), 0);
965   }
966 
967   // Otherwise, softenSetCCOperands returned a scalar, use it.
968   assert((NewRHS.getNode() || NewLHS.getValueType() == N->getValueType(0)) &&
969          "Unexpected setcc expansion!");
970 
971   if (IsStrict) {
972     ReplaceValueWith(SDValue(N, 0), NewLHS);
973     ReplaceValueWith(SDValue(N, 1), Chain);
974     return SDValue();
975   }
976   return NewLHS;
977 }
978 
979 SDValue DAGTypeLegalizer::SoftenFloatOp_STORE(SDNode *N, unsigned OpNo) {
980   assert(ISD::isUNINDEXEDStore(N) && "Indexed store during type legalization!");
981   assert(OpNo == 1 && "Can only soften the stored value!");
982   StoreSDNode *ST = cast<StoreSDNode>(N);
983   SDValue Val = ST->getValue();
984   SDLoc dl(N);
985 
986   if (ST->isTruncatingStore())
987     // Do an FP_ROUND followed by a non-truncating store.
988     Val = BitConvertToInteger(DAG.getNode(ISD::FP_ROUND, dl, ST->getMemoryVT(),
989                                           Val, DAG.getIntPtrConstant(0, dl)));
990   else
991     Val = GetSoftenedFloat(Val);
992 
993   return DAG.getStore(ST->getChain(), dl, Val, ST->getBasePtr(),
994                       ST->getMemOperand());
995 }
996 
997 SDValue DAGTypeLegalizer::SoftenFloatOp_FCOPYSIGN(SDNode *N) {
998   SDValue LHS = N->getOperand(0);
999   SDValue RHS = BitConvertToInteger(N->getOperand(1));
1000   SDLoc dl(N);
1001 
1002   EVT LVT = LHS.getValueType();
1003   EVT ILVT = EVT::getIntegerVT(*DAG.getContext(), LVT.getSizeInBits());
1004   EVT RVT = RHS.getValueType();
1005 
1006   unsigned LSize = LVT.getSizeInBits();
1007   unsigned RSize = RVT.getSizeInBits();
1008 
1009   // Shift right or sign-extend it if the two operands have different types.
1010   int SizeDiff = RSize - LSize;
1011   if (SizeDiff > 0) {
1012     RHS =
1013         DAG.getNode(ISD::SRL, dl, RVT, RHS,
1014                     DAG.getConstant(SizeDiff, dl,
1015                                     TLI.getShiftAmountTy(RHS.getValueType(),
1016                                                          DAG.getDataLayout())));
1017     RHS = DAG.getNode(ISD::TRUNCATE, dl, ILVT, RHS);
1018   } else if (SizeDiff < 0) {
1019     RHS = DAG.getNode(ISD::ANY_EXTEND, dl, LVT, RHS);
1020     RHS =
1021         DAG.getNode(ISD::SHL, dl, ILVT, RHS,
1022                     DAG.getConstant(-SizeDiff, dl,
1023                                     TLI.getShiftAmountTy(RHS.getValueType(),
1024                                                          DAG.getDataLayout())));
1025   }
1026 
1027   RHS = DAG.getBitcast(LVT, RHS);
1028   return DAG.getNode(ISD::FCOPYSIGN, dl, LVT, LHS, RHS);
1029 }
1030 
1031 SDValue DAGTypeLegalizer::SoftenFloatOp_Unary(SDNode *N, RTLIB::Libcall LC) {
1032   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
1033   bool IsStrict = N->isStrictFPOpcode();
1034   unsigned Offset = IsStrict ? 1 : 0;
1035   SDValue Op = GetSoftenedFloat(N->getOperand(0 + Offset));
1036   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1037   TargetLowering::MakeLibCallOptions CallOptions;
1038   EVT OpVT = N->getOperand(0 + Offset).getValueType();
1039   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
1040   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
1041                                                     CallOptions, SDLoc(N),
1042                                                     Chain);
1043   if (IsStrict) {
1044     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1045     ReplaceValueWith(SDValue(N, 0), Tmp.first);
1046     return SDValue();
1047   }
1048 
1049   return Tmp.first;
1050 }
1051 
1052 SDValue DAGTypeLegalizer::SoftenFloatOp_LROUND(SDNode *N) {
1053   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1054   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1055                                              RTLIB::LROUND_F32,
1056                                              RTLIB::LROUND_F64,
1057                                              RTLIB::LROUND_F80,
1058                                              RTLIB::LROUND_F128,
1059                                              RTLIB::LROUND_PPCF128));
1060 }
1061 
1062 SDValue DAGTypeLegalizer::SoftenFloatOp_LLROUND(SDNode *N) {
1063   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1064   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1065                                              RTLIB::LLROUND_F32,
1066                                              RTLIB::LLROUND_F64,
1067                                              RTLIB::LLROUND_F80,
1068                                              RTLIB::LLROUND_F128,
1069                                              RTLIB::LLROUND_PPCF128));
1070 }
1071 
1072 SDValue DAGTypeLegalizer::SoftenFloatOp_LRINT(SDNode *N) {
1073   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1074   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1075                                              RTLIB::LRINT_F32,
1076                                              RTLIB::LRINT_F64,
1077                                              RTLIB::LRINT_F80,
1078                                              RTLIB::LRINT_F128,
1079                                              RTLIB::LRINT_PPCF128));
1080 }
1081 
1082 SDValue DAGTypeLegalizer::SoftenFloatOp_LLRINT(SDNode *N) {
1083   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1084   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1085                                              RTLIB::LLRINT_F32,
1086                                              RTLIB::LLRINT_F64,
1087                                              RTLIB::LLRINT_F80,
1088                                              RTLIB::LLRINT_F128,
1089                                              RTLIB::LLRINT_PPCF128));
1090 }
1091 
1092 //===----------------------------------------------------------------------===//
1093 //  Float Result Expansion
1094 //===----------------------------------------------------------------------===//
1095 
1096 /// ExpandFloatResult - This method is called when the specified result of the
1097 /// specified node is found to need expansion.  At this point, the node may also
1098 /// have invalid operands or may have other results that need promotion, we just
1099 /// know that (at least) one result needs expansion.
1100 void DAGTypeLegalizer::ExpandFloatResult(SDNode *N, unsigned ResNo) {
1101   LLVM_DEBUG(dbgs() << "Expand float result: "; N->dump(&DAG); dbgs() << "\n");
1102   SDValue Lo, Hi;
1103   Lo = Hi = SDValue();
1104 
1105   // See if the target wants to custom expand this node.
1106   if (CustomLowerNode(N, N->getValueType(ResNo), true))
1107     return;
1108 
1109   switch (N->getOpcode()) {
1110   default:
1111 #ifndef NDEBUG
1112     dbgs() << "ExpandFloatResult #" << ResNo << ": ";
1113     N->dump(&DAG); dbgs() << "\n";
1114 #endif
1115     llvm_unreachable("Do not know how to expand the result of this operator!");
1116 
1117   case ISD::UNDEF:        SplitRes_UNDEF(N, Lo, Hi); break;
1118   case ISD::SELECT:       SplitRes_SELECT(N, Lo, Hi); break;
1119   case ISD::SELECT_CC:    SplitRes_SELECT_CC(N, Lo, Hi); break;
1120 
1121   case ISD::MERGE_VALUES:       ExpandRes_MERGE_VALUES(N, ResNo, Lo, Hi); break;
1122   case ISD::BITCAST:            ExpandRes_BITCAST(N, Lo, Hi); break;
1123   case ISD::BUILD_PAIR:         ExpandRes_BUILD_PAIR(N, Lo, Hi); break;
1124   case ISD::EXTRACT_ELEMENT:    ExpandRes_EXTRACT_ELEMENT(N, Lo, Hi); break;
1125   case ISD::EXTRACT_VECTOR_ELT: ExpandRes_EXTRACT_VECTOR_ELT(N, Lo, Hi); break;
1126   case ISD::VAARG:              ExpandRes_VAARG(N, Lo, Hi); break;
1127 
1128   case ISD::ConstantFP: ExpandFloatRes_ConstantFP(N, Lo, Hi); break;
1129   case ISD::FABS:       ExpandFloatRes_FABS(N, Lo, Hi); break;
1130   case ISD::STRICT_FMINNUM:
1131   case ISD::FMINNUM:    ExpandFloatRes_FMINNUM(N, Lo, Hi); break;
1132   case ISD::STRICT_FMAXNUM:
1133   case ISD::FMAXNUM:    ExpandFloatRes_FMAXNUM(N, Lo, Hi); break;
1134   case ISD::STRICT_FADD:
1135   case ISD::FADD:       ExpandFloatRes_FADD(N, Lo, Hi); break;
1136   case ISD::FCBRT:      ExpandFloatRes_FCBRT(N, Lo, Hi); break;
1137   case ISD::STRICT_FCEIL:
1138   case ISD::FCEIL:      ExpandFloatRes_FCEIL(N, Lo, Hi); break;
1139   case ISD::FCOPYSIGN:  ExpandFloatRes_FCOPYSIGN(N, Lo, Hi); break;
1140   case ISD::STRICT_FCOS:
1141   case ISD::FCOS:       ExpandFloatRes_FCOS(N, Lo, Hi); break;
1142   case ISD::STRICT_FDIV:
1143   case ISD::FDIV:       ExpandFloatRes_FDIV(N, Lo, Hi); break;
1144   case ISD::STRICT_FEXP:
1145   case ISD::FEXP:       ExpandFloatRes_FEXP(N, Lo, Hi); break;
1146   case ISD::STRICT_FEXP2:
1147   case ISD::FEXP2:      ExpandFloatRes_FEXP2(N, Lo, Hi); break;
1148   case ISD::STRICT_FFLOOR:
1149   case ISD::FFLOOR:     ExpandFloatRes_FFLOOR(N, Lo, Hi); break;
1150   case ISD::STRICT_FLOG:
1151   case ISD::FLOG:       ExpandFloatRes_FLOG(N, Lo, Hi); break;
1152   case ISD::STRICT_FLOG2:
1153   case ISD::FLOG2:      ExpandFloatRes_FLOG2(N, Lo, Hi); break;
1154   case ISD::STRICT_FLOG10:
1155   case ISD::FLOG10:     ExpandFloatRes_FLOG10(N, Lo, Hi); break;
1156   case ISD::STRICT_FMA:
1157   case ISD::FMA:        ExpandFloatRes_FMA(N, Lo, Hi); break;
1158   case ISD::STRICT_FMUL:
1159   case ISD::FMUL:       ExpandFloatRes_FMUL(N, Lo, Hi); break;
1160   case ISD::STRICT_FNEARBYINT:
1161   case ISD::FNEARBYINT: ExpandFloatRes_FNEARBYINT(N, Lo, Hi); break;
1162   case ISD::FNEG:       ExpandFloatRes_FNEG(N, Lo, Hi); break;
1163   case ISD::STRICT_FP_EXTEND:
1164   case ISD::FP_EXTEND:  ExpandFloatRes_FP_EXTEND(N, Lo, Hi); break;
1165   case ISD::STRICT_FPOW:
1166   case ISD::FPOW:       ExpandFloatRes_FPOW(N, Lo, Hi); break;
1167   case ISD::STRICT_FPOWI:
1168   case ISD::FPOWI:      ExpandFloatRes_FPOWI(N, Lo, Hi); break;
1169   case ISD::STRICT_FRINT:
1170   case ISD::FRINT:      ExpandFloatRes_FRINT(N, Lo, Hi); break;
1171   case ISD::STRICT_FROUND:
1172   case ISD::FROUND:     ExpandFloatRes_FROUND(N, Lo, Hi); break;
1173   case ISD::STRICT_FSIN:
1174   case ISD::FSIN:       ExpandFloatRes_FSIN(N, Lo, Hi); break;
1175   case ISD::STRICT_FSQRT:
1176   case ISD::FSQRT:      ExpandFloatRes_FSQRT(N, Lo, Hi); break;
1177   case ISD::STRICT_FSUB:
1178   case ISD::FSUB:       ExpandFloatRes_FSUB(N, Lo, Hi); break;
1179   case ISD::STRICT_FTRUNC:
1180   case ISD::FTRUNC:     ExpandFloatRes_FTRUNC(N, Lo, Hi); break;
1181   case ISD::LOAD:       ExpandFloatRes_LOAD(N, Lo, Hi); break;
1182   case ISD::SINT_TO_FP:
1183   case ISD::UINT_TO_FP: ExpandFloatRes_XINT_TO_FP(N, Lo, Hi); break;
1184   case ISD::STRICT_FREM:
1185   case ISD::FREM:       ExpandFloatRes_FREM(N, Lo, Hi); break;
1186   }
1187 
1188   // If Lo/Hi is null, the sub-method took care of registering results etc.
1189   if (Lo.getNode())
1190     SetExpandedFloat(SDValue(N, ResNo), Lo, Hi);
1191 }
1192 
1193 void DAGTypeLegalizer::ExpandFloatRes_ConstantFP(SDNode *N, SDValue &Lo,
1194                                                  SDValue &Hi) {
1195   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
1196   assert(NVT.getSizeInBits() == 64 &&
1197          "Do not know how to expand this float constant!");
1198   APInt C = cast<ConstantFPSDNode>(N)->getValueAPF().bitcastToAPInt();
1199   SDLoc dl(N);
1200   Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1201                                  APInt(64, C.getRawData()[1])),
1202                          dl, NVT);
1203   Hi = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1204                                  APInt(64, C.getRawData()[0])),
1205                          dl, NVT);
1206 }
1207 
1208 void DAGTypeLegalizer::ExpandFloatRes_Unary(SDNode *N, RTLIB::Libcall LC,
1209                                             SDValue &Lo, SDValue &Hi) {
1210   bool IsStrict = N->isStrictFPOpcode();
1211   unsigned Offset = IsStrict ? 1 : 0;
1212   SDValue Op = N->getOperand(0 + Offset);
1213   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1214   TargetLowering::MakeLibCallOptions CallOptions;
1215   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, N->getValueType(0),
1216                                                     Op, CallOptions, SDLoc(N),
1217                                                     Chain);
1218   if (IsStrict)
1219     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1220   GetPairElements(Tmp.first, Lo, Hi);
1221 }
1222 
1223 void DAGTypeLegalizer::ExpandFloatRes_Binary(SDNode *N, RTLIB::Libcall LC,
1224                                              SDValue &Lo, SDValue &Hi) {
1225   bool IsStrict = N->isStrictFPOpcode();
1226   unsigned Offset = IsStrict ? 1 : 0;
1227   SDValue Ops[] = { N->getOperand(0 + Offset), N->getOperand(1 + Offset) };
1228   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1229   TargetLowering::MakeLibCallOptions CallOptions;
1230   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, N->getValueType(0),
1231                                                     Ops, CallOptions, SDLoc(N),
1232                                                     Chain);
1233   if (IsStrict)
1234     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1235   GetPairElements(Tmp.first, Lo, Hi);
1236 }
1237 
1238 void DAGTypeLegalizer::ExpandFloatRes_FABS(SDNode *N, SDValue &Lo,
1239                                            SDValue &Hi) {
1240   assert(N->getValueType(0) == MVT::ppcf128 &&
1241          "Logic only correct for ppcf128!");
1242   SDLoc dl(N);
1243   SDValue Tmp;
1244   GetExpandedFloat(N->getOperand(0), Lo, Tmp);
1245   Hi = DAG.getNode(ISD::FABS, dl, Tmp.getValueType(), Tmp);
1246   // Lo = Hi==fabs(Hi) ? Lo : -Lo;
1247   Lo = DAG.getSelectCC(dl, Tmp, Hi, Lo,
1248                    DAG.getNode(ISD::FNEG, dl, Lo.getValueType(), Lo),
1249                    ISD::SETEQ);
1250 }
1251 
1252 void DAGTypeLegalizer::ExpandFloatRes_FMINNUM(SDNode *N, SDValue &Lo,
1253                                               SDValue &Hi) {
1254   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1255                                        RTLIB::FMIN_F32, RTLIB::FMIN_F64,
1256                                        RTLIB::FMIN_F80, RTLIB::FMIN_F128,
1257                                        RTLIB::FMIN_PPCF128), Lo, Hi);
1258 }
1259 
1260 void DAGTypeLegalizer::ExpandFloatRes_FMAXNUM(SDNode *N, SDValue &Lo,
1261                                               SDValue &Hi) {
1262   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1263                                         RTLIB::FMAX_F32, RTLIB::FMAX_F64,
1264                                         RTLIB::FMAX_F80, RTLIB::FMAX_F128,
1265                                         RTLIB::FMAX_PPCF128), Lo, Hi);
1266 }
1267 
1268 void DAGTypeLegalizer::ExpandFloatRes_FADD(SDNode *N, SDValue &Lo,
1269                                            SDValue &Hi) {
1270   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1271                                         RTLIB::ADD_F32, RTLIB::ADD_F64,
1272                                         RTLIB::ADD_F80, RTLIB::ADD_F128,
1273                                         RTLIB::ADD_PPCF128), Lo, Hi);
1274 }
1275 
1276 void DAGTypeLegalizer::ExpandFloatRes_FCBRT(SDNode *N, SDValue &Lo,
1277                                             SDValue &Hi) {
1278   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0), RTLIB::CBRT_F32,
1279                                        RTLIB::CBRT_F64, RTLIB::CBRT_F80,
1280                                        RTLIB::CBRT_F128,
1281                                        RTLIB::CBRT_PPCF128), Lo, Hi);
1282 }
1283 
1284 void DAGTypeLegalizer::ExpandFloatRes_FCEIL(SDNode *N,
1285                                             SDValue &Lo, SDValue &Hi) {
1286   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1287                                        RTLIB::CEIL_F32, RTLIB::CEIL_F64,
1288                                        RTLIB::CEIL_F80, RTLIB::CEIL_F128,
1289                                        RTLIB::CEIL_PPCF128), Lo, Hi);
1290 }
1291 
1292 void DAGTypeLegalizer::ExpandFloatRes_FCOPYSIGN(SDNode *N,
1293                                                 SDValue &Lo, SDValue &Hi) {
1294   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1295                                         RTLIB::COPYSIGN_F32,
1296                                         RTLIB::COPYSIGN_F64,
1297                                         RTLIB::COPYSIGN_F80,
1298                                         RTLIB::COPYSIGN_F128,
1299                                         RTLIB::COPYSIGN_PPCF128), Lo, Hi);
1300 }
1301 
1302 void DAGTypeLegalizer::ExpandFloatRes_FCOS(SDNode *N,
1303                                            SDValue &Lo, SDValue &Hi) {
1304   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1305                                        RTLIB::COS_F32, RTLIB::COS_F64,
1306                                        RTLIB::COS_F80, RTLIB::COS_F128,
1307                                        RTLIB::COS_PPCF128), Lo, Hi);
1308 }
1309 
1310 void DAGTypeLegalizer::ExpandFloatRes_FDIV(SDNode *N, SDValue &Lo,
1311                                            SDValue &Hi) {
1312   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1313                                         RTLIB::DIV_F32,
1314                                         RTLIB::DIV_F64,
1315                                         RTLIB::DIV_F80,
1316                                         RTLIB::DIV_F128,
1317                                         RTLIB::DIV_PPCF128), Lo, Hi);
1318 }
1319 
1320 void DAGTypeLegalizer::ExpandFloatRes_FEXP(SDNode *N,
1321                                            SDValue &Lo, SDValue &Hi) {
1322   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1323                                        RTLIB::EXP_F32, RTLIB::EXP_F64,
1324                                        RTLIB::EXP_F80, RTLIB::EXP_F128,
1325                                        RTLIB::EXP_PPCF128), Lo, Hi);
1326 }
1327 
1328 void DAGTypeLegalizer::ExpandFloatRes_FEXP2(SDNode *N,
1329                                             SDValue &Lo, SDValue &Hi) {
1330   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1331                                        RTLIB::EXP2_F32, RTLIB::EXP2_F64,
1332                                        RTLIB::EXP2_F80, RTLIB::EXP2_F128,
1333                                        RTLIB::EXP2_PPCF128), Lo, Hi);
1334 }
1335 
1336 void DAGTypeLegalizer::ExpandFloatRes_FFLOOR(SDNode *N,
1337                                              SDValue &Lo, SDValue &Hi) {
1338   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1339                                        RTLIB::FLOOR_F32, RTLIB::FLOOR_F64,
1340                                        RTLIB::FLOOR_F80, RTLIB::FLOOR_F128,
1341                                        RTLIB::FLOOR_PPCF128), Lo, Hi);
1342 }
1343 
1344 void DAGTypeLegalizer::ExpandFloatRes_FLOG(SDNode *N,
1345                                            SDValue &Lo, SDValue &Hi) {
1346   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1347                                        RTLIB::LOG_F32, RTLIB::LOG_F64,
1348                                        RTLIB::LOG_F80, RTLIB::LOG_F128,
1349                                        RTLIB::LOG_PPCF128), Lo, Hi);
1350 }
1351 
1352 void DAGTypeLegalizer::ExpandFloatRes_FLOG2(SDNode *N,
1353                                             SDValue &Lo, SDValue &Hi) {
1354   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1355                                        RTLIB::LOG2_F32, RTLIB::LOG2_F64,
1356                                        RTLIB::LOG2_F80, RTLIB::LOG2_F128,
1357                                        RTLIB::LOG2_PPCF128), Lo, Hi);
1358 }
1359 
1360 void DAGTypeLegalizer::ExpandFloatRes_FLOG10(SDNode *N,
1361                                              SDValue &Lo, SDValue &Hi) {
1362   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1363                                        RTLIB::LOG10_F32, RTLIB::LOG10_F64,
1364                                        RTLIB::LOG10_F80, RTLIB::LOG10_F128,
1365                                        RTLIB::LOG10_PPCF128), Lo, Hi);
1366 }
1367 
1368 void DAGTypeLegalizer::ExpandFloatRes_FMA(SDNode *N, SDValue &Lo,
1369                                           SDValue &Hi) {
1370   bool IsStrict = N->isStrictFPOpcode();
1371   unsigned Offset = IsStrict ? 1 : 0;
1372   SDValue Ops[3] = { N->getOperand(0 + Offset), N->getOperand(1 + Offset),
1373                      N->getOperand(2 + Offset) };
1374   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1375   TargetLowering::MakeLibCallOptions CallOptions;
1376   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, GetFPLibCall(N->getValueType(0),
1377                                                    RTLIB::FMA_F32,
1378                                                    RTLIB::FMA_F64,
1379                                                    RTLIB::FMA_F80,
1380                                                    RTLIB::FMA_F128,
1381                                                    RTLIB::FMA_PPCF128),
1382                                  N->getValueType(0), Ops, CallOptions,
1383                                  SDLoc(N), Chain);
1384   if (IsStrict)
1385     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1386   GetPairElements(Tmp.first, Lo, Hi);
1387 }
1388 
1389 void DAGTypeLegalizer::ExpandFloatRes_FMUL(SDNode *N, SDValue &Lo,
1390                                            SDValue &Hi) {
1391   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1392                                                    RTLIB::MUL_F32,
1393                                                    RTLIB::MUL_F64,
1394                                                    RTLIB::MUL_F80,
1395                                                    RTLIB::MUL_F128,
1396                                                    RTLIB::MUL_PPCF128), Lo, Hi);
1397 }
1398 
1399 void DAGTypeLegalizer::ExpandFloatRes_FNEARBYINT(SDNode *N,
1400                                                  SDValue &Lo, SDValue &Hi) {
1401   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1402                                        RTLIB::NEARBYINT_F32,
1403                                        RTLIB::NEARBYINT_F64,
1404                                        RTLIB::NEARBYINT_F80,
1405                                        RTLIB::NEARBYINT_F128,
1406                                        RTLIB::NEARBYINT_PPCF128), Lo, Hi);
1407 }
1408 
1409 void DAGTypeLegalizer::ExpandFloatRes_FNEG(SDNode *N, SDValue &Lo,
1410                                            SDValue &Hi) {
1411   SDLoc dl(N);
1412   GetExpandedFloat(N->getOperand(0), Lo, Hi);
1413   Lo = DAG.getNode(ISD::FNEG, dl, Lo.getValueType(), Lo);
1414   Hi = DAG.getNode(ISD::FNEG, dl, Hi.getValueType(), Hi);
1415 }
1416 
1417 void DAGTypeLegalizer::ExpandFloatRes_FP_EXTEND(SDNode *N, SDValue &Lo,
1418                                                 SDValue &Hi) {
1419   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
1420   SDLoc dl(N);
1421   bool IsStrict = N->isStrictFPOpcode();
1422 
1423   SDValue Chain;
1424   if (IsStrict) {
1425     // If the expanded type is the same as the input type, just bypass the node.
1426     if (NVT == N->getOperand(1).getValueType()) {
1427       Hi = N->getOperand(1);
1428       Chain = N->getOperand(0);
1429     } else {
1430       // Other we need to extend.
1431       Hi = DAG.getNode(ISD::STRICT_FP_EXTEND, dl, { NVT, MVT::Other },
1432                        { N->getOperand(0), N->getOperand(1) });
1433       Chain = Hi.getValue(1);
1434     }
1435   } else {
1436     Hi = DAG.getNode(ISD::FP_EXTEND, dl, NVT, N->getOperand(0));
1437   }
1438 
1439   Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1440                                  APInt(NVT.getSizeInBits(), 0)), dl, NVT);
1441 
1442   if (IsStrict)
1443     ReplaceValueWith(SDValue(N, 1), Chain);
1444 }
1445 
1446 void DAGTypeLegalizer::ExpandFloatRes_FPOW(SDNode *N,
1447                                            SDValue &Lo, SDValue &Hi) {
1448   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1449                                         RTLIB::POW_F32, RTLIB::POW_F64,
1450                                         RTLIB::POW_F80, RTLIB::POW_F128,
1451                                         RTLIB::POW_PPCF128), Lo, Hi);
1452 }
1453 
1454 void DAGTypeLegalizer::ExpandFloatRes_FPOWI(SDNode *N,
1455                                             SDValue &Lo, SDValue &Hi) {
1456   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1457                                         RTLIB::POWI_F32, RTLIB::POWI_F64,
1458                                         RTLIB::POWI_F80, RTLIB::POWI_F128,
1459                                         RTLIB::POWI_PPCF128), Lo, Hi);
1460 }
1461 
1462 void DAGTypeLegalizer::ExpandFloatRes_FREM(SDNode *N,
1463                                            SDValue &Lo, SDValue &Hi) {
1464   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1465                                         RTLIB::REM_F32, RTLIB::REM_F64,
1466                                         RTLIB::REM_F80, RTLIB::REM_F128,
1467                                         RTLIB::REM_PPCF128), Lo, Hi);
1468 }
1469 
1470 void DAGTypeLegalizer::ExpandFloatRes_FRINT(SDNode *N,
1471                                             SDValue &Lo, SDValue &Hi) {
1472   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1473                                        RTLIB::RINT_F32, RTLIB::RINT_F64,
1474                                        RTLIB::RINT_F80, RTLIB::RINT_F128,
1475                                        RTLIB::RINT_PPCF128), Lo, Hi);
1476 }
1477 
1478 void DAGTypeLegalizer::ExpandFloatRes_FROUND(SDNode *N,
1479                                              SDValue &Lo, SDValue &Hi) {
1480   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1481                                        RTLIB::ROUND_F32,
1482                                        RTLIB::ROUND_F64,
1483                                        RTLIB::ROUND_F80,
1484                                        RTLIB::ROUND_F128,
1485                                        RTLIB::ROUND_PPCF128), Lo, Hi);
1486 }
1487 
1488 void DAGTypeLegalizer::ExpandFloatRes_FSIN(SDNode *N,
1489                                            SDValue &Lo, SDValue &Hi) {
1490   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1491                                        RTLIB::SIN_F32, RTLIB::SIN_F64,
1492                                        RTLIB::SIN_F80, RTLIB::SIN_F128,
1493                                        RTLIB::SIN_PPCF128), Lo, Hi);
1494 }
1495 
1496 void DAGTypeLegalizer::ExpandFloatRes_FSQRT(SDNode *N,
1497                                             SDValue &Lo, SDValue &Hi) {
1498   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1499                                        RTLIB::SQRT_F32, RTLIB::SQRT_F64,
1500                                        RTLIB::SQRT_F80, RTLIB::SQRT_F128,
1501                                        RTLIB::SQRT_PPCF128), Lo, Hi);
1502 }
1503 
1504 void DAGTypeLegalizer::ExpandFloatRes_FSUB(SDNode *N, SDValue &Lo,
1505                                            SDValue &Hi) {
1506   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1507                                         RTLIB::SUB_F32,
1508                                         RTLIB::SUB_F64,
1509                                         RTLIB::SUB_F80,
1510                                         RTLIB::SUB_F128,
1511                                         RTLIB::SUB_PPCF128), Lo, Hi);
1512 }
1513 
1514 void DAGTypeLegalizer::ExpandFloatRes_FTRUNC(SDNode *N,
1515                                              SDValue &Lo, SDValue &Hi) {
1516   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1517                                        RTLIB::TRUNC_F32, RTLIB::TRUNC_F64,
1518                                        RTLIB::TRUNC_F80, RTLIB::TRUNC_F128,
1519                                        RTLIB::TRUNC_PPCF128), Lo, Hi);
1520 }
1521 
1522 void DAGTypeLegalizer::ExpandFloatRes_LOAD(SDNode *N, SDValue &Lo,
1523                                            SDValue &Hi) {
1524   if (ISD::isNormalLoad(N)) {
1525     ExpandRes_NormalLoad(N, Lo, Hi);
1526     return;
1527   }
1528 
1529   assert(ISD::isUNINDEXEDLoad(N) && "Indexed load during type legalization!");
1530   LoadSDNode *LD = cast<LoadSDNode>(N);
1531   SDValue Chain = LD->getChain();
1532   SDValue Ptr = LD->getBasePtr();
1533   SDLoc dl(N);
1534 
1535   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), LD->getValueType(0));
1536   assert(NVT.isByteSized() && "Expanded type not byte sized!");
1537   assert(LD->getMemoryVT().bitsLE(NVT) && "Float type not round?");
1538 
1539   Hi = DAG.getExtLoad(LD->getExtensionType(), dl, NVT, Chain, Ptr,
1540                       LD->getMemoryVT(), LD->getMemOperand());
1541 
1542   // Remember the chain.
1543   Chain = Hi.getValue(1);
1544 
1545   // The low part is zero.
1546   Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1547                                  APInt(NVT.getSizeInBits(), 0)), dl, NVT);
1548 
1549   // Modified the chain - switch anything that used the old chain to use the
1550   // new one.
1551   ReplaceValueWith(SDValue(LD, 1), Chain);
1552 }
1553 
1554 void DAGTypeLegalizer::ExpandFloatRes_XINT_TO_FP(SDNode *N, SDValue &Lo,
1555                                                  SDValue &Hi) {
1556   assert(N->getValueType(0) == MVT::ppcf128 && "Unsupported XINT_TO_FP!");
1557   EVT VT = N->getValueType(0);
1558   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
1559   SDValue Src = N->getOperand(0);
1560   EVT SrcVT = Src.getValueType();
1561   bool isSigned = N->getOpcode() == ISD::SINT_TO_FP;
1562   SDLoc dl(N);
1563 
1564   // First do an SINT_TO_FP, whether the original was signed or unsigned.
1565   // When promoting partial word types to i32 we must honor the signedness,
1566   // though.
1567   if (SrcVT.bitsLE(MVT::i32)) {
1568     // The integer can be represented exactly in an f64.
1569     Src = DAG.getNode(isSigned ? ISD::SIGN_EXTEND : ISD::ZERO_EXTEND, dl,
1570                       MVT::i32, Src);
1571     Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1572                                    APInt(NVT.getSizeInBits(), 0)), dl, NVT);
1573     Hi = DAG.getNode(ISD::SINT_TO_FP, dl, NVT, Src);
1574   } else {
1575     RTLIB::Libcall LC = RTLIB::UNKNOWN_LIBCALL;
1576     if (SrcVT.bitsLE(MVT::i64)) {
1577       Src = DAG.getNode(isSigned ? ISD::SIGN_EXTEND : ISD::ZERO_EXTEND, dl,
1578                         MVT::i64, Src);
1579       LC = RTLIB::SINTTOFP_I64_PPCF128;
1580     } else if (SrcVT.bitsLE(MVT::i128)) {
1581       Src = DAG.getNode(ISD::SIGN_EXTEND, dl, MVT::i128, Src);
1582       LC = RTLIB::SINTTOFP_I128_PPCF128;
1583     }
1584     assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported XINT_TO_FP!");
1585 
1586     TargetLowering::MakeLibCallOptions CallOptions;
1587     CallOptions.setSExt(true);
1588     Hi = TLI.makeLibCall(DAG, LC, VT, Src, CallOptions, dl).first;
1589     GetPairElements(Hi, Lo, Hi);
1590   }
1591 
1592   if (isSigned)
1593     return;
1594 
1595   // Unsigned - fix up the SINT_TO_FP value just calculated.
1596   Hi = DAG.getNode(ISD::BUILD_PAIR, dl, VT, Lo, Hi);
1597   SrcVT = Src.getValueType();
1598 
1599   // x>=0 ? (ppcf128)(iN)x : (ppcf128)(iN)x + 2^N; N=32,64,128.
1600   static const uint64_t TwoE32[]  = { 0x41f0000000000000LL, 0 };
1601   static const uint64_t TwoE64[]  = { 0x43f0000000000000LL, 0 };
1602   static const uint64_t TwoE128[] = { 0x47f0000000000000LL, 0 };
1603   ArrayRef<uint64_t> Parts;
1604 
1605   switch (SrcVT.getSimpleVT().SimpleTy) {
1606   default:
1607     llvm_unreachable("Unsupported UINT_TO_FP!");
1608   case MVT::i32:
1609     Parts = TwoE32;
1610     break;
1611   case MVT::i64:
1612     Parts = TwoE64;
1613     break;
1614   case MVT::i128:
1615     Parts = TwoE128;
1616     break;
1617   }
1618 
1619   // TODO: Are there fast-math-flags to propagate to this FADD?
1620   Lo = DAG.getNode(ISD::FADD, dl, VT, Hi,
1621                    DAG.getConstantFP(APFloat(APFloat::PPCDoubleDouble(),
1622                                              APInt(128, Parts)),
1623                                      dl, MVT::ppcf128));
1624   Lo = DAG.getSelectCC(dl, Src, DAG.getConstant(0, dl, SrcVT),
1625                        Lo, Hi, ISD::SETLT);
1626   GetPairElements(Lo, Lo, Hi);
1627 }
1628 
1629 
1630 //===----------------------------------------------------------------------===//
1631 //  Float Operand Expansion
1632 //===----------------------------------------------------------------------===//
1633 
1634 /// ExpandFloatOperand - This method is called when the specified operand of the
1635 /// specified node is found to need expansion.  At this point, all of the result
1636 /// types of the node are known to be legal, but other operands of the node may
1637 /// need promotion or expansion as well as the specified one.
1638 bool DAGTypeLegalizer::ExpandFloatOperand(SDNode *N, unsigned OpNo) {
1639   LLVM_DEBUG(dbgs() << "Expand float operand: "; N->dump(&DAG); dbgs() << "\n");
1640   SDValue Res = SDValue();
1641 
1642   // See if the target wants to custom expand this node.
1643   if (CustomLowerNode(N, N->getOperand(OpNo).getValueType(), false))
1644     return false;
1645 
1646   switch (N->getOpcode()) {
1647   default:
1648 #ifndef NDEBUG
1649     dbgs() << "ExpandFloatOperand Op #" << OpNo << ": ";
1650     N->dump(&DAG); dbgs() << "\n";
1651 #endif
1652     llvm_unreachable("Do not know how to expand this operator's operand!");
1653 
1654   case ISD::BITCAST:         Res = ExpandOp_BITCAST(N); break;
1655   case ISD::BUILD_VECTOR:    Res = ExpandOp_BUILD_VECTOR(N); break;
1656   case ISD::EXTRACT_ELEMENT: Res = ExpandOp_EXTRACT_ELEMENT(N); break;
1657 
1658   case ISD::BR_CC:      Res = ExpandFloatOp_BR_CC(N); break;
1659   case ISD::FCOPYSIGN:  Res = ExpandFloatOp_FCOPYSIGN(N); break;
1660   case ISD::STRICT_FP_ROUND:
1661   case ISD::FP_ROUND:   Res = ExpandFloatOp_FP_ROUND(N); break;
1662   case ISD::STRICT_FP_TO_SINT:
1663   case ISD::FP_TO_SINT: Res = ExpandFloatOp_FP_TO_SINT(N); break;
1664   case ISD::STRICT_FP_TO_UINT:
1665   case ISD::FP_TO_UINT: Res = ExpandFloatOp_FP_TO_UINT(N); break;
1666   case ISD::LROUND:     Res = ExpandFloatOp_LROUND(N); break;
1667   case ISD::LLROUND:    Res = ExpandFloatOp_LLROUND(N); break;
1668   case ISD::LRINT:      Res = ExpandFloatOp_LRINT(N); break;
1669   case ISD::LLRINT:     Res = ExpandFloatOp_LLRINT(N); break;
1670   case ISD::SELECT_CC:  Res = ExpandFloatOp_SELECT_CC(N); break;
1671   case ISD::SETCC:      Res = ExpandFloatOp_SETCC(N); break;
1672   case ISD::STORE:      Res = ExpandFloatOp_STORE(cast<StoreSDNode>(N),
1673                                                   OpNo); break;
1674   }
1675 
1676   // If the result is null, the sub-method took care of registering results etc.
1677   if (!Res.getNode()) return false;
1678 
1679   // If the result is N, the sub-method updated N in place.  Tell the legalizer
1680   // core about this.
1681   if (Res.getNode() == N)
1682     return true;
1683 
1684   assert(Res.getValueType() == N->getValueType(0) && N->getNumValues() == 1 &&
1685          "Invalid operand expansion");
1686 
1687   ReplaceValueWith(SDValue(N, 0), Res);
1688   return false;
1689 }
1690 
1691 /// FloatExpandSetCCOperands - Expand the operands of a comparison.  This code
1692 /// is shared among BR_CC, SELECT_CC, and SETCC handlers.
1693 void DAGTypeLegalizer::FloatExpandSetCCOperands(SDValue &NewLHS,
1694                                                 SDValue &NewRHS,
1695                                                 ISD::CondCode &CCCode,
1696                                                 const SDLoc &dl) {
1697   SDValue LHSLo, LHSHi, RHSLo, RHSHi;
1698   GetExpandedFloat(NewLHS, LHSLo, LHSHi);
1699   GetExpandedFloat(NewRHS, RHSLo, RHSHi);
1700 
1701   assert(NewLHS.getValueType() == MVT::ppcf128 && "Unsupported setcc type!");
1702 
1703   // FIXME:  This generated code sucks.  We want to generate
1704   //         FCMPU crN, hi1, hi2
1705   //         BNE crN, L:
1706   //         FCMPU crN, lo1, lo2
1707   // The following can be improved, but not that much.
1708   SDValue Tmp1, Tmp2, Tmp3;
1709   Tmp1 = DAG.getSetCC(dl, getSetCCResultType(LHSHi.getValueType()),
1710                       LHSHi, RHSHi, ISD::SETOEQ);
1711   Tmp2 = DAG.getSetCC(dl, getSetCCResultType(LHSLo.getValueType()),
1712                       LHSLo, RHSLo, CCCode);
1713   Tmp3 = DAG.getNode(ISD::AND, dl, Tmp1.getValueType(), Tmp1, Tmp2);
1714   Tmp1 = DAG.getSetCC(dl, getSetCCResultType(LHSHi.getValueType()),
1715                       LHSHi, RHSHi, ISD::SETUNE);
1716   Tmp2 = DAG.getSetCC(dl, getSetCCResultType(LHSHi.getValueType()),
1717                       LHSHi, RHSHi, CCCode);
1718   Tmp1 = DAG.getNode(ISD::AND, dl, Tmp1.getValueType(), Tmp1, Tmp2);
1719   NewLHS = DAG.getNode(ISD::OR, dl, Tmp1.getValueType(), Tmp1, Tmp3);
1720   NewRHS = SDValue();   // LHS is the result, not a compare.
1721 }
1722 
1723 SDValue DAGTypeLegalizer::ExpandFloatOp_BR_CC(SDNode *N) {
1724   SDValue NewLHS = N->getOperand(2), NewRHS = N->getOperand(3);
1725   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(1))->get();
1726   FloatExpandSetCCOperands(NewLHS, NewRHS, CCCode, SDLoc(N));
1727 
1728   // If ExpandSetCCOperands returned a scalar, we need to compare the result
1729   // against zero to select between true and false values.
1730   if (!NewRHS.getNode()) {
1731     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
1732     CCCode = ISD::SETNE;
1733   }
1734 
1735   // Update N to have the operands specified.
1736   return SDValue(DAG.UpdateNodeOperands(N, N->getOperand(0),
1737                                 DAG.getCondCode(CCCode), NewLHS, NewRHS,
1738                                 N->getOperand(4)), 0);
1739 }
1740 
1741 SDValue DAGTypeLegalizer::ExpandFloatOp_FCOPYSIGN(SDNode *N) {
1742   assert(N->getOperand(1).getValueType() == MVT::ppcf128 &&
1743          "Logic only correct for ppcf128!");
1744   SDValue Lo, Hi;
1745   GetExpandedFloat(N->getOperand(1), Lo, Hi);
1746   // The ppcf128 value is providing only the sign; take it from the
1747   // higher-order double (which must have the larger magnitude).
1748   return DAG.getNode(ISD::FCOPYSIGN, SDLoc(N),
1749                      N->getValueType(0), N->getOperand(0), Hi);
1750 }
1751 
1752 SDValue DAGTypeLegalizer::ExpandFloatOp_FP_ROUND(SDNode *N) {
1753   bool IsStrict = N->isStrictFPOpcode();
1754   assert(N->getOperand(IsStrict ? 1 : 0).getValueType() == MVT::ppcf128 &&
1755          "Logic only correct for ppcf128!");
1756   SDValue Lo, Hi;
1757   GetExpandedFloat(N->getOperand(IsStrict ? 1 : 0), Lo, Hi);
1758 
1759   if (!IsStrict)
1760     // Round it the rest of the way (e.g. to f32) if needed.
1761     return DAG.getNode(ISD::FP_ROUND, SDLoc(N),
1762                        N->getValueType(0), Hi, N->getOperand(1));
1763 
1764   // Eliminate the node if the input float type is the same as the output float
1765   // type.
1766   if (Hi.getValueType() == N->getValueType(0)) {
1767     // Connect the output chain to the input chain, unlinking the node.
1768     ReplaceValueWith(SDValue(N, 1), N->getOperand(0));
1769     ReplaceValueWith(SDValue(N, 0), Hi);
1770     return SDValue();
1771   }
1772 
1773   SDValue Expansion = DAG.getNode(ISD::STRICT_FP_ROUND, SDLoc(N),
1774                                   {N->getValueType(0), MVT::Other},
1775                                   {N->getOperand(0), Hi, N->getOperand(2)});
1776   ReplaceValueWith(SDValue(N, 1), Expansion.getValue(1));
1777   ReplaceValueWith(SDValue(N, 0), Expansion);
1778   return SDValue();
1779 }
1780 
1781 SDValue DAGTypeLegalizer::ExpandFloatOp_FP_TO_SINT(SDNode *N) {
1782   EVT RVT = N->getValueType(0);
1783   SDLoc dl(N);
1784 
1785   bool IsStrict = N->isStrictFPOpcode();
1786   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
1787   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1788   RTLIB::Libcall LC = RTLIB::getFPTOSINT(Op.getValueType(), RVT);
1789   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_TO_SINT!");
1790   TargetLowering::MakeLibCallOptions CallOptions;
1791   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, RVT, Op,
1792                                                     CallOptions, dl, Chain);
1793   if (!IsStrict)
1794     return Tmp.first;
1795 
1796   ReplaceValueWith(SDValue(N, 1), Tmp.second);
1797   ReplaceValueWith(SDValue(N, 0), Tmp.first);
1798   return SDValue();
1799 }
1800 
1801 SDValue DAGTypeLegalizer::ExpandFloatOp_FP_TO_UINT(SDNode *N) {
1802   EVT RVT = N->getValueType(0);
1803   SDLoc dl(N);
1804 
1805   bool IsStrict = N->isStrictFPOpcode();
1806   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
1807   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1808   RTLIB::Libcall LC = RTLIB::getFPTOUINT(Op.getValueType(), RVT);
1809   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_TO_UINT!");
1810   TargetLowering::MakeLibCallOptions CallOptions;
1811   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, RVT, Op,
1812                                                     CallOptions, dl, Chain);
1813   if (!IsStrict)
1814     return Tmp.first;
1815 
1816   ReplaceValueWith(SDValue(N, 1), Tmp.second);
1817   ReplaceValueWith(SDValue(N, 0), Tmp.first);
1818   return SDValue();
1819 }
1820 
1821 SDValue DAGTypeLegalizer::ExpandFloatOp_SELECT_CC(SDNode *N) {
1822   SDValue NewLHS = N->getOperand(0), NewRHS = N->getOperand(1);
1823   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(4))->get();
1824   FloatExpandSetCCOperands(NewLHS, NewRHS, CCCode, SDLoc(N));
1825 
1826   // If ExpandSetCCOperands returned a scalar, we need to compare the result
1827   // against zero to select between true and false values.
1828   if (!NewRHS.getNode()) {
1829     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
1830     CCCode = ISD::SETNE;
1831   }
1832 
1833   // Update N to have the operands specified.
1834   return SDValue(DAG.UpdateNodeOperands(N, NewLHS, NewRHS,
1835                                 N->getOperand(2), N->getOperand(3),
1836                                 DAG.getCondCode(CCCode)), 0);
1837 }
1838 
1839 SDValue DAGTypeLegalizer::ExpandFloatOp_SETCC(SDNode *N) {
1840   SDValue NewLHS = N->getOperand(0), NewRHS = N->getOperand(1);
1841   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(2))->get();
1842   FloatExpandSetCCOperands(NewLHS, NewRHS, CCCode, SDLoc(N));
1843 
1844   // If ExpandSetCCOperands returned a scalar, use it.
1845   if (!NewRHS.getNode()) {
1846     assert(NewLHS.getValueType() == N->getValueType(0) &&
1847            "Unexpected setcc expansion!");
1848     return NewLHS;
1849   }
1850 
1851   // Otherwise, update N to have the operands specified.
1852   return SDValue(DAG.UpdateNodeOperands(N, NewLHS, NewRHS,
1853                                 DAG.getCondCode(CCCode)), 0);
1854 }
1855 
1856 SDValue DAGTypeLegalizer::ExpandFloatOp_STORE(SDNode *N, unsigned OpNo) {
1857   if (ISD::isNormalStore(N))
1858     return ExpandOp_NormalStore(N, OpNo);
1859 
1860   assert(ISD::isUNINDEXEDStore(N) && "Indexed store during type legalization!");
1861   assert(OpNo == 1 && "Can only expand the stored value so far");
1862   StoreSDNode *ST = cast<StoreSDNode>(N);
1863 
1864   SDValue Chain = ST->getChain();
1865   SDValue Ptr = ST->getBasePtr();
1866 
1867   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(),
1868                                      ST->getValue().getValueType());
1869   assert(NVT.isByteSized() && "Expanded type not byte sized!");
1870   assert(ST->getMemoryVT().bitsLE(NVT) && "Float type not round?");
1871   (void)NVT;
1872 
1873   SDValue Lo, Hi;
1874   GetExpandedOp(ST->getValue(), Lo, Hi);
1875 
1876   return DAG.getTruncStore(Chain, SDLoc(N), Hi, Ptr,
1877                            ST->getMemoryVT(), ST->getMemOperand());
1878 }
1879 
1880 SDValue DAGTypeLegalizer::ExpandFloatOp_LROUND(SDNode *N) {
1881   EVT RVT = N->getValueType(0);
1882   EVT RetVT = N->getOperand(0).getValueType();
1883   TargetLowering::MakeLibCallOptions CallOptions;
1884   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
1885                                            RTLIB::LROUND_F32,
1886                                            RTLIB::LROUND_F64,
1887                                            RTLIB::LROUND_F80,
1888                                            RTLIB::LROUND_F128,
1889                                            RTLIB::LROUND_PPCF128),
1890                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
1891 }
1892 
1893 SDValue DAGTypeLegalizer::ExpandFloatOp_LLROUND(SDNode *N) {
1894   EVT RVT = N->getValueType(0);
1895   EVT RetVT = N->getOperand(0).getValueType();
1896   TargetLowering::MakeLibCallOptions CallOptions;
1897   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
1898                                            RTLIB::LLROUND_F32,
1899                                            RTLIB::LLROUND_F64,
1900                                            RTLIB::LLROUND_F80,
1901                                            RTLIB::LLROUND_F128,
1902                                            RTLIB::LLROUND_PPCF128),
1903                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
1904 }
1905 
1906 SDValue DAGTypeLegalizer::ExpandFloatOp_LRINT(SDNode *N) {
1907   EVT RVT = N->getValueType(0);
1908   EVT RetVT = N->getOperand(0).getValueType();
1909   TargetLowering::MakeLibCallOptions CallOptions;
1910   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
1911                                            RTLIB::LRINT_F32,
1912                                            RTLIB::LRINT_F64,
1913                                            RTLIB::LRINT_F80,
1914                                            RTLIB::LRINT_F128,
1915                                            RTLIB::LRINT_PPCF128),
1916                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
1917 }
1918 
1919 SDValue DAGTypeLegalizer::ExpandFloatOp_LLRINT(SDNode *N) {
1920   EVT RVT = N->getValueType(0);
1921   EVT RetVT = N->getOperand(0).getValueType();
1922   TargetLowering::MakeLibCallOptions CallOptions;
1923   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
1924                                            RTLIB::LLRINT_F32,
1925                                            RTLIB::LLRINT_F64,
1926                                            RTLIB::LLRINT_F80,
1927                                            RTLIB::LLRINT_F128,
1928                                            RTLIB::LLRINT_PPCF128),
1929                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
1930 }
1931 
1932 //===----------------------------------------------------------------------===//
1933 //  Float Operand Promotion
1934 //===----------------------------------------------------------------------===//
1935 //
1936 
1937 static ISD::NodeType GetPromotionOpcode(EVT OpVT, EVT RetVT) {
1938   if (OpVT == MVT::f16) {
1939       return ISD::FP16_TO_FP;
1940   } else if (RetVT == MVT::f16) {
1941       return ISD::FP_TO_FP16;
1942   }
1943 
1944   report_fatal_error("Attempt at an invalid promotion-related conversion");
1945 }
1946 
1947 bool DAGTypeLegalizer::PromoteFloatOperand(SDNode *N, unsigned OpNo) {
1948   LLVM_DEBUG(dbgs() << "Promote float operand " << OpNo << ": "; N->dump(&DAG);
1949              dbgs() << "\n");
1950   SDValue R = SDValue();
1951 
1952   if (CustomLowerNode(N, N->getOperand(OpNo).getValueType(), false)) {
1953     LLVM_DEBUG(dbgs() << "Node has been custom lowered, done\n");
1954     return false;
1955   }
1956 
1957   // Nodes that use a promotion-requiring floating point operand, but doesn't
1958   // produce a promotion-requiring floating point result, need to be legalized
1959   // to use the promoted float operand.  Nodes that produce at least one
1960   // promotion-requiring floating point result have their operands legalized as
1961   // a part of PromoteFloatResult.
1962   switch (N->getOpcode()) {
1963     default:
1964   #ifndef NDEBUG
1965       dbgs() << "PromoteFloatOperand Op #" << OpNo << ": ";
1966       N->dump(&DAG); dbgs() << "\n";
1967   #endif
1968       llvm_unreachable("Do not know how to promote this operator's operand!");
1969 
1970     case ISD::BITCAST:    R = PromoteFloatOp_BITCAST(N, OpNo); break;
1971     case ISD::FCOPYSIGN:  R = PromoteFloatOp_FCOPYSIGN(N, OpNo); break;
1972     case ISD::FP_TO_SINT:
1973     case ISD::FP_TO_UINT: R = PromoteFloatOp_FP_TO_XINT(N, OpNo); break;
1974     case ISD::FP_EXTEND:  R = PromoteFloatOp_FP_EXTEND(N, OpNo); break;
1975     case ISD::SELECT_CC:  R = PromoteFloatOp_SELECT_CC(N, OpNo); break;
1976     case ISD::SETCC:      R = PromoteFloatOp_SETCC(N, OpNo); break;
1977     case ISD::STORE:      R = PromoteFloatOp_STORE(N, OpNo); break;
1978   }
1979 
1980   if (R.getNode())
1981     ReplaceValueWith(SDValue(N, 0), R);
1982   return false;
1983 }
1984 
1985 SDValue DAGTypeLegalizer::PromoteFloatOp_BITCAST(SDNode *N, unsigned OpNo) {
1986   SDValue Op = N->getOperand(0);
1987   EVT OpVT = Op->getValueType(0);
1988 
1989   SDValue Promoted = GetPromotedFloat(N->getOperand(0));
1990   EVT PromotedVT = Promoted->getValueType(0);
1991 
1992   // Convert the promoted float value to the desired IVT.
1993   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), OpVT.getSizeInBits());
1994   SDValue Convert = DAG.getNode(GetPromotionOpcode(PromotedVT, OpVT), SDLoc(N),
1995                                 IVT, Promoted);
1996   // The final result type might not be an scalar so we need a bitcast. The
1997   // bitcast will be further legalized if needed.
1998   return DAG.getBitcast(N->getValueType(0), Convert);
1999 }
2000 
2001 // Promote Operand 1 of FCOPYSIGN.  Operand 0 ought to be handled by
2002 // PromoteFloatRes_FCOPYSIGN.
2003 SDValue DAGTypeLegalizer::PromoteFloatOp_FCOPYSIGN(SDNode *N, unsigned OpNo) {
2004   assert (OpNo == 1 && "Only Operand 1 must need promotion here");
2005   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2006 
2007   return DAG.getNode(N->getOpcode(), SDLoc(N), N->getValueType(0),
2008                      N->getOperand(0), Op1);
2009 }
2010 
2011 // Convert the promoted float value to the desired integer type
2012 SDValue DAGTypeLegalizer::PromoteFloatOp_FP_TO_XINT(SDNode *N, unsigned OpNo) {
2013   SDValue Op = GetPromotedFloat(N->getOperand(0));
2014   return DAG.getNode(N->getOpcode(), SDLoc(N), N->getValueType(0), Op);
2015 }
2016 
2017 SDValue DAGTypeLegalizer::PromoteFloatOp_FP_EXTEND(SDNode *N, unsigned OpNo) {
2018   SDValue Op = GetPromotedFloat(N->getOperand(0));
2019   EVT VT = N->getValueType(0);
2020 
2021   // Desired VT is same as promoted type.  Use promoted float directly.
2022   if (VT == Op->getValueType(0))
2023     return Op;
2024 
2025   // Else, extend the promoted float value to the desired VT.
2026   return DAG.getNode(ISD::FP_EXTEND, SDLoc(N), VT, Op);
2027 }
2028 
2029 // Promote the float operands used for comparison.  The true- and false-
2030 // operands have the same type as the result and are promoted, if needed, by
2031 // PromoteFloatRes_SELECT_CC
2032 SDValue DAGTypeLegalizer::PromoteFloatOp_SELECT_CC(SDNode *N, unsigned OpNo) {
2033   SDValue LHS = GetPromotedFloat(N->getOperand(0));
2034   SDValue RHS = GetPromotedFloat(N->getOperand(1));
2035 
2036   return DAG.getNode(ISD::SELECT_CC, SDLoc(N), N->getValueType(0),
2037                      LHS, RHS, N->getOperand(2), N->getOperand(3),
2038                      N->getOperand(4));
2039 }
2040 
2041 // Construct a SETCC that compares the promoted values and sets the conditional
2042 // code.
2043 SDValue DAGTypeLegalizer::PromoteFloatOp_SETCC(SDNode *N, unsigned OpNo) {
2044   EVT VT = N->getValueType(0);
2045   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2046   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2047   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(2))->get();
2048 
2049   return DAG.getSetCC(SDLoc(N), VT, Op0, Op1, CCCode);
2050 
2051 }
2052 
2053 // Lower the promoted Float down to the integer value of same size and construct
2054 // a STORE of the integer value.
2055 SDValue DAGTypeLegalizer::PromoteFloatOp_STORE(SDNode *N, unsigned OpNo) {
2056   StoreSDNode *ST = cast<StoreSDNode>(N);
2057   SDValue Val = ST->getValue();
2058   SDLoc DL(N);
2059 
2060   SDValue Promoted = GetPromotedFloat(Val);
2061   EVT VT = ST->getOperand(1).getValueType();
2062   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2063 
2064   SDValue NewVal;
2065   NewVal = DAG.getNode(GetPromotionOpcode(Promoted.getValueType(), VT), DL,
2066                        IVT, Promoted);
2067 
2068   return DAG.getStore(ST->getChain(), DL, NewVal, ST->getBasePtr(),
2069                       ST->getMemOperand());
2070 }
2071 
2072 //===----------------------------------------------------------------------===//
2073 //  Float Result Promotion
2074 //===----------------------------------------------------------------------===//
2075 
2076 void DAGTypeLegalizer::PromoteFloatResult(SDNode *N, unsigned ResNo) {
2077   LLVM_DEBUG(dbgs() << "Promote float result " << ResNo << ": "; N->dump(&DAG);
2078              dbgs() << "\n");
2079   SDValue R = SDValue();
2080 
2081   // See if the target wants to custom expand this node.
2082   if (CustomLowerNode(N, N->getValueType(ResNo), true)) {
2083     LLVM_DEBUG(dbgs() << "Node has been custom expanded, done\n");
2084     return;
2085   }
2086 
2087   switch (N->getOpcode()) {
2088     // These opcodes cannot appear if promotion of FP16 is done in the backend
2089     // instead of Clang
2090     case ISD::FP16_TO_FP:
2091     case ISD::FP_TO_FP16:
2092     default:
2093 #ifndef NDEBUG
2094       dbgs() << "PromoteFloatResult #" << ResNo << ": ";
2095       N->dump(&DAG); dbgs() << "\n";
2096 #endif
2097       llvm_unreachable("Do not know how to promote this operator's result!");
2098 
2099     case ISD::BITCAST:    R = PromoteFloatRes_BITCAST(N); break;
2100     case ISD::ConstantFP: R = PromoteFloatRes_ConstantFP(N); break;
2101     case ISD::EXTRACT_VECTOR_ELT:
2102                           R = PromoteFloatRes_EXTRACT_VECTOR_ELT(N); break;
2103     case ISD::FCOPYSIGN:  R = PromoteFloatRes_FCOPYSIGN(N); break;
2104 
2105     // Unary FP Operations
2106     case ISD::FABS:
2107     case ISD::FCBRT:
2108     case ISD::FCEIL:
2109     case ISD::FCOS:
2110     case ISD::FEXP:
2111     case ISD::FEXP2:
2112     case ISD::FFLOOR:
2113     case ISD::FLOG:
2114     case ISD::FLOG2:
2115     case ISD::FLOG10:
2116     case ISD::FNEARBYINT:
2117     case ISD::FNEG:
2118     case ISD::FRINT:
2119     case ISD::FROUND:
2120     case ISD::FSIN:
2121     case ISD::FSQRT:
2122     case ISD::FTRUNC:
2123     case ISD::FCANONICALIZE: R = PromoteFloatRes_UnaryOp(N); break;
2124 
2125     // Binary FP Operations
2126     case ISD::FADD:
2127     case ISD::FDIV:
2128     case ISD::FMAXIMUM:
2129     case ISD::FMINIMUM:
2130     case ISD::FMAXNUM:
2131     case ISD::FMINNUM:
2132     case ISD::FMUL:
2133     case ISD::FPOW:
2134     case ISD::FREM:
2135     case ISD::FSUB:       R = PromoteFloatRes_BinOp(N); break;
2136 
2137     case ISD::FMA:        // FMA is same as FMAD
2138     case ISD::FMAD:       R = PromoteFloatRes_FMAD(N); break;
2139 
2140     case ISD::FPOWI:      R = PromoteFloatRes_FPOWI(N); break;
2141 
2142     case ISD::FP_ROUND:   R = PromoteFloatRes_FP_ROUND(N); break;
2143     case ISD::LOAD:       R = PromoteFloatRes_LOAD(N); break;
2144     case ISD::SELECT:     R = PromoteFloatRes_SELECT(N); break;
2145     case ISD::SELECT_CC:  R = PromoteFloatRes_SELECT_CC(N); break;
2146 
2147     case ISD::SINT_TO_FP:
2148     case ISD::UINT_TO_FP: R = PromoteFloatRes_XINT_TO_FP(N); break;
2149     case ISD::UNDEF:      R = PromoteFloatRes_UNDEF(N); break;
2150     case ISD::ATOMIC_SWAP: R = BitcastToInt_ATOMIC_SWAP(N); break;
2151   }
2152 
2153   if (R.getNode())
2154     SetPromotedFloat(SDValue(N, ResNo), R);
2155 }
2156 
2157 // Bitcast from i16 to f16:  convert the i16 to a f32 value instead.
2158 // At this point, it is not possible to determine if the bitcast value is
2159 // eventually stored to memory or promoted to f32 or promoted to a floating
2160 // point at a higher precision.  Some of these cases are handled by FP_EXTEND,
2161 // STORE promotion handlers.
2162 SDValue DAGTypeLegalizer::PromoteFloatRes_BITCAST(SDNode *N) {
2163   EVT VT = N->getValueType(0);
2164   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2165   // Input type isn't guaranteed to be a scalar int so bitcast if not. The
2166   // bitcast will be legalized further if necessary.
2167   EVT IVT = EVT::getIntegerVT(*DAG.getContext(),
2168                               N->getOperand(0).getValueType().getSizeInBits());
2169   SDValue Cast = DAG.getBitcast(IVT, N->getOperand(0));
2170   return DAG.getNode(GetPromotionOpcode(VT, NVT), SDLoc(N), NVT, Cast);
2171 }
2172 
2173 SDValue DAGTypeLegalizer::PromoteFloatRes_ConstantFP(SDNode *N) {
2174   ConstantFPSDNode *CFPNode = cast<ConstantFPSDNode>(N);
2175   EVT VT = N->getValueType(0);
2176   SDLoc DL(N);
2177 
2178   // Get the (bit-cast) APInt of the APFloat and build an integer constant
2179   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2180   SDValue C = DAG.getConstant(CFPNode->getValueAPF().bitcastToAPInt(), DL,
2181                               IVT);
2182 
2183   // Convert the Constant to the desired FP type
2184   // FIXME We might be able to do the conversion during compilation and get rid
2185   // of it from the object code
2186   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2187   return DAG.getNode(GetPromotionOpcode(VT, NVT), DL, NVT, C);
2188 }
2189 
2190 // If the Index operand is a constant, try to redirect the extract operation to
2191 // the correct legalized vector.  If not, bit-convert the input vector to
2192 // equivalent integer vector.  Extract the element as an (bit-cast) integer
2193 // value and convert it to the promoted type.
2194 SDValue DAGTypeLegalizer::PromoteFloatRes_EXTRACT_VECTOR_ELT(SDNode *N) {
2195   SDLoc DL(N);
2196 
2197   // If the index is constant, try to extract the value from the legalized
2198   // vector type.
2199   if (isa<ConstantSDNode>(N->getOperand(1))) {
2200     SDValue Vec = N->getOperand(0);
2201     SDValue Idx = N->getOperand(1);
2202     EVT VecVT = Vec->getValueType(0);
2203     EVT EltVT = VecVT.getVectorElementType();
2204 
2205     uint64_t IdxVal = cast<ConstantSDNode>(Idx)->getZExtValue();
2206 
2207     switch (getTypeAction(VecVT)) {
2208     default: break;
2209     case TargetLowering::TypeScalarizeVector: {
2210       SDValue Res = GetScalarizedVector(N->getOperand(0));
2211       ReplaceValueWith(SDValue(N, 0), Res);
2212       return SDValue();
2213     }
2214     case TargetLowering::TypeWidenVector: {
2215       Vec = GetWidenedVector(Vec);
2216       SDValue Res = DAG.getNode(N->getOpcode(), DL, EltVT, Vec, Idx);
2217       ReplaceValueWith(SDValue(N, 0), Res);
2218       return SDValue();
2219     }
2220     case TargetLowering::TypeSplitVector: {
2221       SDValue Lo, Hi;
2222       GetSplitVector(Vec, Lo, Hi);
2223 
2224       uint64_t LoElts = Lo.getValueType().getVectorNumElements();
2225       SDValue Res;
2226       if (IdxVal < LoElts)
2227         Res = DAG.getNode(N->getOpcode(), DL, EltVT, Lo, Idx);
2228       else
2229         Res = DAG.getNode(N->getOpcode(), DL, EltVT, Hi,
2230                           DAG.getConstant(IdxVal - LoElts, DL,
2231                                           Idx.getValueType()));
2232       ReplaceValueWith(SDValue(N, 0), Res);
2233       return SDValue();
2234     }
2235 
2236     }
2237   }
2238 
2239   // Bit-convert the input vector to the equivalent integer vector
2240   SDValue NewOp = BitConvertVectorToIntegerVector(N->getOperand(0));
2241   EVT IVT = NewOp.getValueType().getVectorElementType();
2242 
2243   // Extract the element as an (bit-cast) integer value
2244   SDValue NewVal = DAG.getNode(ISD::EXTRACT_VECTOR_ELT, DL, IVT,
2245                                NewOp, N->getOperand(1));
2246 
2247   // Convert the element to the desired FP type
2248   EVT VT = N->getValueType(0);
2249   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2250   return DAG.getNode(GetPromotionOpcode(VT, NVT), SDLoc(N), NVT, NewVal);
2251 }
2252 
2253 // FCOPYSIGN(X, Y) returns the value of X with the sign of Y.  If the result
2254 // needs promotion, so does the argument X.  Note that Y, if needed, will be
2255 // handled during operand promotion.
2256 SDValue DAGTypeLegalizer::PromoteFloatRes_FCOPYSIGN(SDNode *N) {
2257   EVT VT = N->getValueType(0);
2258   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2259   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2260 
2261   SDValue Op1 = N->getOperand(1);
2262 
2263   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1);
2264 }
2265 
2266 // Unary operation where the result and the operand have PromoteFloat type
2267 // action.  Construct a new SDNode with the promoted float value of the old
2268 // operand.
2269 SDValue DAGTypeLegalizer::PromoteFloatRes_UnaryOp(SDNode *N) {
2270   EVT VT = N->getValueType(0);
2271   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2272   SDValue Op = GetPromotedFloat(N->getOperand(0));
2273 
2274   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op);
2275 }
2276 
2277 // Binary operations where the result and both operands have PromoteFloat type
2278 // action.  Construct a new SDNode with the promoted float values of the old
2279 // operands.
2280 SDValue DAGTypeLegalizer::PromoteFloatRes_BinOp(SDNode *N) {
2281   EVT VT = N->getValueType(0);
2282   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2283   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2284   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2285   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1, N->getFlags());
2286 }
2287 
2288 SDValue DAGTypeLegalizer::PromoteFloatRes_FMAD(SDNode *N) {
2289   EVT VT = N->getValueType(0);
2290   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2291   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2292   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2293   SDValue Op2 = GetPromotedFloat(N->getOperand(2));
2294 
2295   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1, Op2);
2296 }
2297 
2298 // Promote the Float (first) operand and retain the Integer (second) operand
2299 SDValue DAGTypeLegalizer::PromoteFloatRes_FPOWI(SDNode *N) {
2300   EVT VT = N->getValueType(0);
2301   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2302   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2303   SDValue Op1 = N->getOperand(1);
2304 
2305   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1);
2306 }
2307 
2308 // Explicit operation to reduce precision.  Reduce the value to half precision
2309 // and promote it back to the legal type.
2310 SDValue DAGTypeLegalizer::PromoteFloatRes_FP_ROUND(SDNode *N) {
2311   SDLoc DL(N);
2312 
2313   SDValue Op = N->getOperand(0);
2314   EVT VT = N->getValueType(0);
2315   EVT OpVT = Op->getValueType(0);
2316   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
2317   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2318 
2319   // Round promoted float to desired precision
2320   SDValue Round = DAG.getNode(GetPromotionOpcode(OpVT, VT), DL, IVT, Op);
2321   // Promote it back to the legal output type
2322   return DAG.getNode(GetPromotionOpcode(VT, NVT), DL, NVT, Round);
2323 }
2324 
2325 SDValue DAGTypeLegalizer::PromoteFloatRes_LOAD(SDNode *N) {
2326   LoadSDNode *L = cast<LoadSDNode>(N);
2327   EVT VT = N->getValueType(0);
2328 
2329   // Load the value as an integer value with the same number of bits.
2330   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2331   SDValue newL = DAG.getLoad(L->getAddressingMode(), L->getExtensionType(), IVT,
2332                              SDLoc(N), L->getChain(), L->getBasePtr(),
2333                              L->getOffset(), L->getPointerInfo(), IVT,
2334                              L->getAlignment(),
2335                              L->getMemOperand()->getFlags(),
2336                              L->getAAInfo());
2337   // Legalize the chain result by replacing uses of the old value chain with the
2338   // new one
2339   ReplaceValueWith(SDValue(N, 1), newL.getValue(1));
2340 
2341   // Convert the integer value to the desired FP type
2342   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2343   return DAG.getNode(GetPromotionOpcode(VT, NVT), SDLoc(N), NVT, newL);
2344 }
2345 
2346 // Construct a new SELECT node with the promoted true- and false- values.
2347 SDValue DAGTypeLegalizer::PromoteFloatRes_SELECT(SDNode *N) {
2348   SDValue TrueVal = GetPromotedFloat(N->getOperand(1));
2349   SDValue FalseVal = GetPromotedFloat(N->getOperand(2));
2350 
2351   return DAG.getNode(ISD::SELECT, SDLoc(N), TrueVal->getValueType(0),
2352                      N->getOperand(0), TrueVal, FalseVal);
2353 }
2354 
2355 // Construct a new SELECT_CC node with the promoted true- and false- values.
2356 // The operands used for comparison are promoted by PromoteFloatOp_SELECT_CC.
2357 SDValue DAGTypeLegalizer::PromoteFloatRes_SELECT_CC(SDNode *N) {
2358   SDValue TrueVal = GetPromotedFloat(N->getOperand(2));
2359   SDValue FalseVal = GetPromotedFloat(N->getOperand(3));
2360 
2361   return DAG.getNode(ISD::SELECT_CC, SDLoc(N),
2362                      TrueVal.getNode()->getValueType(0), N->getOperand(0),
2363                      N->getOperand(1), TrueVal, FalseVal, N->getOperand(4));
2364 }
2365 
2366 // Construct a SDNode that transforms the SINT or UINT operand to the promoted
2367 // float type.
2368 SDValue DAGTypeLegalizer::PromoteFloatRes_XINT_TO_FP(SDNode *N) {
2369   SDLoc DL(N);
2370   EVT VT = N->getValueType(0);
2371   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2372   SDValue NV = DAG.getNode(N->getOpcode(), DL, NVT, N->getOperand(0));
2373   // Round the value to the desired precision (that of the source type).
2374   return DAG.getNode(
2375       ISD::FP_EXTEND, DL, NVT,
2376       DAG.getNode(ISD::FP_ROUND, DL, VT, NV, DAG.getIntPtrConstant(0, DL)));
2377 }
2378 
2379 SDValue DAGTypeLegalizer::PromoteFloatRes_UNDEF(SDNode *N) {
2380   return DAG.getUNDEF(TLI.getTypeToTransformTo(*DAG.getContext(),
2381                                                N->getValueType(0)));
2382 }
2383 
2384 SDValue DAGTypeLegalizer::BitcastToInt_ATOMIC_SWAP(SDNode *N) {
2385   EVT VT = N->getValueType(0);
2386 
2387   AtomicSDNode *AM = cast<AtomicSDNode>(N);
2388   SDLoc SL(N);
2389 
2390   SDValue CastVal = BitConvertToInteger(AM->getVal());
2391   EVT CastVT = CastVal.getValueType();
2392 
2393   SDValue NewAtomic
2394     = DAG.getAtomic(ISD::ATOMIC_SWAP, SL, CastVT,
2395                     DAG.getVTList(CastVT, MVT::Other),
2396                     { AM->getChain(), AM->getBasePtr(), CastVal },
2397                     AM->getMemOperand());
2398 
2399   SDValue Result = NewAtomic;
2400 
2401   if (getTypeAction(VT) == TargetLowering::TypePromoteFloat) {
2402     EVT NFPVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2403     Result = DAG.getNode(GetPromotionOpcode(VT, NFPVT), SL, NFPVT,
2404                                      NewAtomic);
2405   }
2406 
2407   // Legalize the chain result by replacing uses of the old value chain with the
2408   // new one
2409   ReplaceValueWith(SDValue(N, 1), NewAtomic.getValue(1));
2410 
2411   return Result;
2412 
2413 }
2414 
2415