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_FROUNDEVEN:
117     case ISD::FROUNDEVEN:  R = SoftenFloatRes_FROUNDEVEN(N); break;
118     case ISD::STRICT_FSIN:
119     case ISD::FSIN:        R = SoftenFloatRes_FSIN(N); break;
120     case ISD::STRICT_FSQRT:
121     case ISD::FSQRT:       R = SoftenFloatRes_FSQRT(N); break;
122     case ISD::STRICT_FSUB:
123     case ISD::FSUB:        R = SoftenFloatRes_FSUB(N); break;
124     case ISD::STRICT_FTRUNC:
125     case ISD::FTRUNC:      R = SoftenFloatRes_FTRUNC(N); break;
126     case ISD::LOAD:        R = SoftenFloatRes_LOAD(N); break;
127     case ISD::ATOMIC_SWAP: R = BitcastToInt_ATOMIC_SWAP(N); break;
128     case ISD::SELECT:      R = SoftenFloatRes_SELECT(N); break;
129     case ISD::SELECT_CC:   R = SoftenFloatRes_SELECT_CC(N); break;
130     case ISD::FREEZE:      R = SoftenFloatRes_FREEZE(N); break;
131     case ISD::STRICT_SINT_TO_FP:
132     case ISD::STRICT_UINT_TO_FP:
133     case ISD::SINT_TO_FP:
134     case ISD::UINT_TO_FP:  R = SoftenFloatRes_XINT_TO_FP(N); break;
135     case ISD::UNDEF:       R = SoftenFloatRes_UNDEF(N); break;
136     case ISD::VAARG:       R = SoftenFloatRes_VAARG(N); break;
137     case ISD::VECREDUCE_FADD:
138     case ISD::VECREDUCE_FMUL:
139     case ISD::VECREDUCE_FMIN:
140     case ISD::VECREDUCE_FMAX:
141       R = SoftenFloatRes_VECREDUCE(N);
142       break;
143     case ISD::VECREDUCE_SEQ_FADD:
144     case ISD::VECREDUCE_SEQ_FMUL:
145       R = SoftenFloatRes_VECREDUCE_SEQ(N);
146       break;
147   }
148 
149   // If R is null, the sub-method took care of registering the result.
150   if (R.getNode()) {
151     assert(R.getNode() != N);
152     SetSoftenedFloat(SDValue(N, ResNo), R);
153   }
154 }
155 
156 SDValue DAGTypeLegalizer::SoftenFloatRes_Unary(SDNode *N, RTLIB::Libcall LC) {
157   bool IsStrict = N->isStrictFPOpcode();
158   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
159   unsigned Offset = IsStrict ? 1 : 0;
160   assert(N->getNumOperands() == (1 + Offset) &&
161          "Unexpected number of operands!");
162   SDValue Op = GetSoftenedFloat(N->getOperand(0 + Offset));
163   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
164   TargetLowering::MakeLibCallOptions CallOptions;
165   EVT OpVT = N->getOperand(0 + Offset).getValueType();
166   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
167   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
168                                                     CallOptions, SDLoc(N),
169                                                     Chain);
170   if (IsStrict)
171     ReplaceValueWith(SDValue(N, 1), Tmp.second);
172   return Tmp.first;
173 }
174 
175 SDValue DAGTypeLegalizer::SoftenFloatRes_Binary(SDNode *N, RTLIB::Libcall LC) {
176   bool IsStrict = N->isStrictFPOpcode();
177   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
178   unsigned Offset = IsStrict ? 1 : 0;
179   assert(N->getNumOperands() == (2 + Offset) &&
180          "Unexpected number of operands!");
181   SDValue Ops[2] = { GetSoftenedFloat(N->getOperand(0 + Offset)),
182                      GetSoftenedFloat(N->getOperand(1 + Offset)) };
183   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
184   TargetLowering::MakeLibCallOptions CallOptions;
185   EVT OpsVT[2] = { N->getOperand(0 + Offset).getValueType(),
186                    N->getOperand(1 + Offset).getValueType() };
187   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
188   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Ops,
189                                                     CallOptions, SDLoc(N),
190                                                     Chain);
191   if (IsStrict)
192     ReplaceValueWith(SDValue(N, 1), Tmp.second);
193   return Tmp.first;
194 }
195 
196 SDValue DAGTypeLegalizer::SoftenFloatRes_BITCAST(SDNode *N) {
197   return BitConvertToInteger(N->getOperand(0));
198 }
199 
200 SDValue DAGTypeLegalizer::SoftenFloatRes_FREEZE(SDNode *N) {
201   EVT Ty = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
202   return DAG.getNode(ISD::FREEZE, SDLoc(N), Ty,
203                      GetSoftenedFloat(N->getOperand(0)));
204 }
205 
206 SDValue DAGTypeLegalizer::SoftenFloatRes_MERGE_VALUES(SDNode *N,
207                                                       unsigned ResNo) {
208   SDValue Op = DisintegrateMERGE_VALUES(N, ResNo);
209   return BitConvertToInteger(Op);
210 }
211 
212 SDValue DAGTypeLegalizer::SoftenFloatRes_BUILD_PAIR(SDNode *N) {
213   // Convert the inputs to integers, and build a new pair out of them.
214   return DAG.getNode(ISD::BUILD_PAIR, SDLoc(N),
215                      TLI.getTypeToTransformTo(*DAG.getContext(),
216                                               N->getValueType(0)),
217                      BitConvertToInteger(N->getOperand(0)),
218                      BitConvertToInteger(N->getOperand(1)));
219 }
220 
221 SDValue DAGTypeLegalizer::SoftenFloatRes_ConstantFP(SDNode *N) {
222   ConstantFPSDNode *CN = cast<ConstantFPSDNode>(N);
223   // In ppcf128, the high 64 bits are always first in memory regardless
224   // of Endianness. LLVM's APFloat representation is not Endian sensitive,
225   // and so always converts into a 128-bit APInt in a non-Endian-sensitive
226   // way. However, APInt's are serialized in an Endian-sensitive fashion,
227   // so on big-Endian targets, the two doubles are output in the wrong
228   // order. Fix this by manually flipping the order of the high 64 bits
229   // and the low 64 bits here.
230   if (DAG.getDataLayout().isBigEndian() &&
231       CN->getValueType(0).getSimpleVT() == llvm::MVT::ppcf128) {
232     uint64_t words[2] = { CN->getValueAPF().bitcastToAPInt().getRawData()[1],
233                           CN->getValueAPF().bitcastToAPInt().getRawData()[0] };
234     APInt Val(128, words);
235     return DAG.getConstant(Val, SDLoc(CN),
236                            TLI.getTypeToTransformTo(*DAG.getContext(),
237                                                     CN->getValueType(0)));
238   } else {
239     return DAG.getConstant(CN->getValueAPF().bitcastToAPInt(), SDLoc(CN),
240                            TLI.getTypeToTransformTo(*DAG.getContext(),
241                                                     CN->getValueType(0)));
242   }
243 }
244 
245 SDValue DAGTypeLegalizer::SoftenFloatRes_EXTRACT_VECTOR_ELT(SDNode *N, unsigned ResNo) {
246   SDValue NewOp = BitConvertVectorToIntegerVector(N->getOperand(0));
247   return DAG.getNode(ISD::EXTRACT_VECTOR_ELT, SDLoc(N),
248                      NewOp.getValueType().getVectorElementType(),
249                      NewOp, N->getOperand(1));
250 }
251 
252 SDValue DAGTypeLegalizer::SoftenFloatRes_FABS(SDNode *N) {
253   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
254   unsigned Size = NVT.getSizeInBits();
255 
256   // Mask = ~(1 << (Size-1))
257   APInt API = APInt::getAllOnesValue(Size);
258   API.clearBit(Size - 1);
259   SDValue Mask = DAG.getConstant(API, SDLoc(N), NVT);
260   SDValue Op = GetSoftenedFloat(N->getOperand(0));
261   return DAG.getNode(ISD::AND, SDLoc(N), NVT, Op, Mask);
262 }
263 
264 SDValue DAGTypeLegalizer::SoftenFloatRes_FMINNUM(SDNode *N) {
265   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
266                                                RTLIB::FMIN_F32,
267                                                RTLIB::FMIN_F64,
268                                                RTLIB::FMIN_F80,
269                                                RTLIB::FMIN_F128,
270                                                RTLIB::FMIN_PPCF128));
271 }
272 
273 SDValue DAGTypeLegalizer::SoftenFloatRes_FMAXNUM(SDNode *N) {
274   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
275                                                RTLIB::FMAX_F32,
276                                                RTLIB::FMAX_F64,
277                                                RTLIB::FMAX_F80,
278                                                RTLIB::FMAX_F128,
279                                                RTLIB::FMAX_PPCF128));
280 }
281 
282 SDValue DAGTypeLegalizer::SoftenFloatRes_FADD(SDNode *N) {
283   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
284                                                RTLIB::ADD_F32,
285                                                RTLIB::ADD_F64,
286                                                RTLIB::ADD_F80,
287                                                RTLIB::ADD_F128,
288                                                RTLIB::ADD_PPCF128));
289 }
290 
291 SDValue DAGTypeLegalizer::SoftenFloatRes_FCBRT(SDNode *N) {
292   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
293                                            RTLIB::CBRT_F32,
294                                            RTLIB::CBRT_F64,
295                                            RTLIB::CBRT_F80,
296                                            RTLIB::CBRT_F128,
297                                            RTLIB::CBRT_PPCF128));
298 }
299 
300 SDValue DAGTypeLegalizer::SoftenFloatRes_FCEIL(SDNode *N) {
301   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
302                                               RTLIB::CEIL_F32,
303                                               RTLIB::CEIL_F64,
304                                               RTLIB::CEIL_F80,
305                                               RTLIB::CEIL_F128,
306                                               RTLIB::CEIL_PPCF128));
307 }
308 
309 SDValue DAGTypeLegalizer::SoftenFloatRes_FCOPYSIGN(SDNode *N) {
310   SDValue LHS = GetSoftenedFloat(N->getOperand(0));
311   SDValue RHS = BitConvertToInteger(N->getOperand(1));
312   SDLoc dl(N);
313 
314   EVT LVT = LHS.getValueType();
315   EVT RVT = RHS.getValueType();
316 
317   unsigned LSize = LVT.getSizeInBits();
318   unsigned RSize = RVT.getSizeInBits();
319 
320   // First get the sign bit of second operand.
321   SDValue SignBit = DAG.getNode(
322       ISD::SHL, dl, RVT, DAG.getConstant(1, dl, RVT),
323       DAG.getConstant(RSize - 1, dl,
324                       TLI.getShiftAmountTy(RVT, DAG.getDataLayout())));
325   SignBit = DAG.getNode(ISD::AND, dl, RVT, RHS, SignBit);
326 
327   // Shift right or sign-extend it if the two operands have different types.
328   int SizeDiff = RVT.getSizeInBits() - LVT.getSizeInBits();
329   if (SizeDiff > 0) {
330     SignBit =
331         DAG.getNode(ISD::SRL, dl, RVT, SignBit,
332                     DAG.getConstant(SizeDiff, dl,
333                                     TLI.getShiftAmountTy(SignBit.getValueType(),
334                                                          DAG.getDataLayout())));
335     SignBit = DAG.getNode(ISD::TRUNCATE, dl, LVT, SignBit);
336   } else if (SizeDiff < 0) {
337     SignBit = DAG.getNode(ISD::ANY_EXTEND, dl, LVT, SignBit);
338     SignBit =
339         DAG.getNode(ISD::SHL, dl, LVT, SignBit,
340                     DAG.getConstant(-SizeDiff, dl,
341                                     TLI.getShiftAmountTy(SignBit.getValueType(),
342                                                          DAG.getDataLayout())));
343   }
344 
345   // Clear the sign bit of the first operand.
346   SDValue Mask = DAG.getNode(
347       ISD::SHL, dl, LVT, DAG.getConstant(1, dl, LVT),
348       DAG.getConstant(LSize - 1, dl,
349                       TLI.getShiftAmountTy(LVT, DAG.getDataLayout())));
350   Mask = DAG.getNode(ISD::SUB, dl, LVT, Mask, DAG.getConstant(1, dl, LVT));
351   LHS = DAG.getNode(ISD::AND, dl, LVT, LHS, Mask);
352 
353   // Or the value with the sign bit.
354   return DAG.getNode(ISD::OR, dl, LVT, LHS, SignBit);
355 }
356 
357 SDValue DAGTypeLegalizer::SoftenFloatRes_FCOS(SDNode *N) {
358   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
359                                               RTLIB::COS_F32,
360                                               RTLIB::COS_F64,
361                                               RTLIB::COS_F80,
362                                               RTLIB::COS_F128,
363                                               RTLIB::COS_PPCF128));
364 }
365 
366 SDValue DAGTypeLegalizer::SoftenFloatRes_FDIV(SDNode *N) {
367   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
368                                                RTLIB::DIV_F32,
369                                                RTLIB::DIV_F64,
370                                                RTLIB::DIV_F80,
371                                                RTLIB::DIV_F128,
372                                                RTLIB::DIV_PPCF128));
373 }
374 
375 SDValue DAGTypeLegalizer::SoftenFloatRes_FEXP(SDNode *N) {
376   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
377                                               RTLIB::EXP_F32,
378                                               RTLIB::EXP_F64,
379                                               RTLIB::EXP_F80,
380                                               RTLIB::EXP_F128,
381                                               RTLIB::EXP_PPCF128));
382 }
383 
384 SDValue DAGTypeLegalizer::SoftenFloatRes_FEXP2(SDNode *N) {
385   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
386                                               RTLIB::EXP2_F32,
387                                               RTLIB::EXP2_F64,
388                                               RTLIB::EXP2_F80,
389                                               RTLIB::EXP2_F128,
390                                               RTLIB::EXP2_PPCF128));
391 }
392 
393 SDValue DAGTypeLegalizer::SoftenFloatRes_FFLOOR(SDNode *N) {
394   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
395                                               RTLIB::FLOOR_F32,
396                                               RTLIB::FLOOR_F64,
397                                               RTLIB::FLOOR_F80,
398                                               RTLIB::FLOOR_F128,
399                                               RTLIB::FLOOR_PPCF128));
400 }
401 
402 SDValue DAGTypeLegalizer::SoftenFloatRes_FLOG(SDNode *N) {
403   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
404                                               RTLIB::LOG_F32,
405                                               RTLIB::LOG_F64,
406                                               RTLIB::LOG_F80,
407                                               RTLIB::LOG_F128,
408                                               RTLIB::LOG_PPCF128));
409 }
410 
411 SDValue DAGTypeLegalizer::SoftenFloatRes_FLOG2(SDNode *N) {
412   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
413                                               RTLIB::LOG2_F32,
414                                               RTLIB::LOG2_F64,
415                                               RTLIB::LOG2_F80,
416                                               RTLIB::LOG2_F128,
417                                               RTLIB::LOG2_PPCF128));
418 }
419 
420 SDValue DAGTypeLegalizer::SoftenFloatRes_FLOG10(SDNode *N) {
421   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
422                                               RTLIB::LOG10_F32,
423                                               RTLIB::LOG10_F64,
424                                               RTLIB::LOG10_F80,
425                                               RTLIB::LOG10_F128,
426                                               RTLIB::LOG10_PPCF128));
427 }
428 
429 SDValue DAGTypeLegalizer::SoftenFloatRes_FMA(SDNode *N) {
430   bool IsStrict = N->isStrictFPOpcode();
431   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
432   unsigned Offset = IsStrict ? 1 : 0;
433   SDValue Ops[3] = { GetSoftenedFloat(N->getOperand(0 + Offset)),
434                      GetSoftenedFloat(N->getOperand(1 + Offset)),
435                      GetSoftenedFloat(N->getOperand(2 + Offset)) };
436   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
437   TargetLowering::MakeLibCallOptions CallOptions;
438   EVT OpsVT[3] = { N->getOperand(0 + Offset).getValueType(),
439                    N->getOperand(1 + Offset).getValueType(),
440                    N->getOperand(2 + Offset).getValueType() };
441   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
442   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG,
443                                                     GetFPLibCall(N->getValueType(0),
444                                                                  RTLIB::FMA_F32,
445                                                                  RTLIB::FMA_F64,
446                                                                  RTLIB::FMA_F80,
447                                                                  RTLIB::FMA_F128,
448                                                                  RTLIB::FMA_PPCF128),
449                          NVT, Ops, CallOptions, SDLoc(N), Chain);
450   if (IsStrict)
451     ReplaceValueWith(SDValue(N, 1), Tmp.second);
452   return Tmp.first;
453 }
454 
455 SDValue DAGTypeLegalizer::SoftenFloatRes_FMUL(SDNode *N) {
456   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
457                                                RTLIB::MUL_F32,
458                                                RTLIB::MUL_F64,
459                                                RTLIB::MUL_F80,
460                                                RTLIB::MUL_F128,
461                                                RTLIB::MUL_PPCF128));
462 }
463 
464 SDValue DAGTypeLegalizer::SoftenFloatRes_FNEARBYINT(SDNode *N) {
465   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
466                                               RTLIB::NEARBYINT_F32,
467                                               RTLIB::NEARBYINT_F64,
468                                               RTLIB::NEARBYINT_F80,
469                                               RTLIB::NEARBYINT_F128,
470                                               RTLIB::NEARBYINT_PPCF128));
471 }
472 
473 SDValue DAGTypeLegalizer::SoftenFloatRes_FNEG(SDNode *N) {
474   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
475   SDLoc dl(N);
476 
477   // Expand Y = FNEG(X) -> Y = X ^ sign mask
478   APInt SignMask = APInt::getSignMask(NVT.getSizeInBits());
479   return DAG.getNode(ISD::XOR, dl, NVT, GetSoftenedFloat(N->getOperand(0)),
480                      DAG.getConstant(SignMask, dl, NVT));
481 }
482 
483 SDValue DAGTypeLegalizer::SoftenFloatRes_FP_EXTEND(SDNode *N) {
484   bool IsStrict = N->isStrictFPOpcode();
485   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
486   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
487 
488   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
489 
490   if (getTypeAction(Op.getValueType()) == TargetLowering::TypePromoteFloat) {
491     Op = GetPromotedFloat(Op);
492     // If the promotion did the FP_EXTEND to the destination type for us,
493     // there's nothing left to do here.
494     if (Op.getValueType() == N->getValueType(0))
495       return BitConvertToInteger(Op);
496   }
497 
498   // There's only a libcall for f16 -> f32, so proceed in two stages. Also, it's
499   // entirely possible for both f16 and f32 to be legal, so use the fully
500   // hard-float FP_EXTEND rather than FP16_TO_FP.
501   if (Op.getValueType() == MVT::f16 && N->getValueType(0) != MVT::f32) {
502     if (IsStrict) {
503       Op = DAG.getNode(ISD::STRICT_FP_EXTEND, SDLoc(N),
504                        { MVT::f32, MVT::Other }, { Chain, Op });
505       Chain = Op.getValue(1);
506     } else {
507       Op = DAG.getNode(ISD::FP_EXTEND, SDLoc(N), MVT::f32, Op);
508     }
509   }
510 
511   RTLIB::Libcall LC = RTLIB::getFPEXT(Op.getValueType(), N->getValueType(0));
512   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_EXTEND!");
513   TargetLowering::MakeLibCallOptions CallOptions;
514   EVT OpVT = N->getOperand(IsStrict ? 1 : 0).getValueType();
515   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
516   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
517                                                     CallOptions, SDLoc(N),
518                                                     Chain);
519   if (IsStrict)
520     ReplaceValueWith(SDValue(N, 1), Tmp.second);
521   return Tmp.first;
522 }
523 
524 // FIXME: Should we just use 'normal' FP_EXTEND / FP_TRUNC instead of special
525 // nodes?
526 SDValue DAGTypeLegalizer::SoftenFloatRes_FP16_TO_FP(SDNode *N) {
527   EVT MidVT = TLI.getTypeToTransformTo(*DAG.getContext(), MVT::f32);
528   SDValue Op = N->getOperand(0);
529   TargetLowering::MakeLibCallOptions CallOptions;
530   EVT OpsVT[1] = { N->getOperand(0).getValueType() };
531   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
532   SDValue Res32 = TLI.makeLibCall(DAG, RTLIB::FPEXT_F16_F32, MidVT, Op,
533                                   CallOptions, SDLoc(N)).first;
534   if (N->getValueType(0) == MVT::f32)
535     return Res32;
536 
537   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
538   RTLIB::Libcall LC = RTLIB::getFPEXT(MVT::f32, N->getValueType(0));
539   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_EXTEND!");
540   return TLI.makeLibCall(DAG, LC, NVT, Res32, CallOptions, SDLoc(N)).first;
541 }
542 
543 SDValue DAGTypeLegalizer::SoftenFloatRes_FP_ROUND(SDNode *N) {
544   bool IsStrict = N->isStrictFPOpcode();
545   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
546   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
547   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
548   RTLIB::Libcall LC = RTLIB::getFPROUND(Op.getValueType(), N->getValueType(0));
549   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_ROUND!");
550   TargetLowering::MakeLibCallOptions CallOptions;
551   EVT OpVT = N->getOperand(IsStrict ? 1 : 0).getValueType();
552   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
553   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
554                                                     CallOptions, SDLoc(N),
555                                                     Chain);
556   if (IsStrict)
557     ReplaceValueWith(SDValue(N, 1), Tmp.second);
558   return Tmp.first;
559 }
560 
561 SDValue DAGTypeLegalizer::SoftenFloatRes_FPOW(SDNode *N) {
562   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
563                                                RTLIB::POW_F32,
564                                                RTLIB::POW_F64,
565                                                RTLIB::POW_F80,
566                                                RTLIB::POW_F128,
567                                                RTLIB::POW_PPCF128));
568 }
569 
570 SDValue DAGTypeLegalizer::SoftenFloatRes_FPOWI(SDNode *N) {
571   bool IsStrict = N->isStrictFPOpcode();
572   unsigned Offset = IsStrict ? 1 : 0;
573   assert(N->getOperand(1 + Offset).getValueType() == MVT::i32 &&
574          "Unsupported power type!");
575   RTLIB::Libcall LC = GetFPLibCall(N->getValueType(0),
576                                    RTLIB::POWI_F32,
577                                    RTLIB::POWI_F64,
578                                    RTLIB::POWI_F80,
579                                    RTLIB::POWI_F128,
580                                    RTLIB::POWI_PPCF128);
581   if (!TLI.getLibcallName(LC)) {
582     // Some targets don't have a powi libcall; use pow instead.
583     // FIXME: Implement this if some target needs it.
584     DAG.getContext()->emitError("Don't know how to soften fpowi to fpow");
585     return DAG.getUNDEF(N->getValueType(0));
586   }
587 
588   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
589   SDValue Ops[2] = { GetSoftenedFloat(N->getOperand(0 + Offset)),
590                      N->getOperand(1 + Offset) };
591   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
592   TargetLowering::MakeLibCallOptions CallOptions;
593   EVT OpsVT[2] = { N->getOperand(0 + Offset).getValueType(),
594                    N->getOperand(1 + Offset).getValueType() };
595   CallOptions.setTypeListBeforeSoften(OpsVT, N->getValueType(0), true);
596   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Ops,
597                                                     CallOptions, SDLoc(N),
598                                                     Chain);
599   if (IsStrict)
600     ReplaceValueWith(SDValue(N, 1), Tmp.second);
601   return Tmp.first;
602 }
603 
604 SDValue DAGTypeLegalizer::SoftenFloatRes_FREM(SDNode *N) {
605   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
606                                                RTLIB::REM_F32,
607                                                RTLIB::REM_F64,
608                                                RTLIB::REM_F80,
609                                                RTLIB::REM_F128,
610                                                RTLIB::REM_PPCF128));
611 }
612 
613 SDValue DAGTypeLegalizer::SoftenFloatRes_FRINT(SDNode *N) {
614   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
615                                               RTLIB::RINT_F32,
616                                               RTLIB::RINT_F64,
617                                               RTLIB::RINT_F80,
618                                               RTLIB::RINT_F128,
619                                               RTLIB::RINT_PPCF128));
620 }
621 
622 SDValue DAGTypeLegalizer::SoftenFloatRes_FROUND(SDNode *N) {
623   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
624                                               RTLIB::ROUND_F32,
625                                               RTLIB::ROUND_F64,
626                                               RTLIB::ROUND_F80,
627                                               RTLIB::ROUND_F128,
628                                               RTLIB::ROUND_PPCF128));
629 }
630 
631 SDValue DAGTypeLegalizer::SoftenFloatRes_FROUNDEVEN(SDNode *N) {
632   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
633                                               RTLIB::ROUNDEVEN_F32,
634                                               RTLIB::ROUNDEVEN_F64,
635                                               RTLIB::ROUNDEVEN_F80,
636                                               RTLIB::ROUNDEVEN_F128,
637                                               RTLIB::ROUNDEVEN_PPCF128));
638 }
639 
640 SDValue DAGTypeLegalizer::SoftenFloatRes_FSIN(SDNode *N) {
641   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
642                                               RTLIB::SIN_F32,
643                                               RTLIB::SIN_F64,
644                                               RTLIB::SIN_F80,
645                                               RTLIB::SIN_F128,
646                                               RTLIB::SIN_PPCF128));
647 }
648 
649 SDValue DAGTypeLegalizer::SoftenFloatRes_FSQRT(SDNode *N) {
650   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
651                                               RTLIB::SQRT_F32,
652                                               RTLIB::SQRT_F64,
653                                               RTLIB::SQRT_F80,
654                                               RTLIB::SQRT_F128,
655                                               RTLIB::SQRT_PPCF128));
656 }
657 
658 SDValue DAGTypeLegalizer::SoftenFloatRes_FSUB(SDNode *N) {
659   return SoftenFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
660                                                RTLIB::SUB_F32,
661                                                RTLIB::SUB_F64,
662                                                RTLIB::SUB_F80,
663                                                RTLIB::SUB_F128,
664                                                RTLIB::SUB_PPCF128));
665 }
666 
667 SDValue DAGTypeLegalizer::SoftenFloatRes_FTRUNC(SDNode *N) {
668   return SoftenFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
669                                               RTLIB::TRUNC_F32,
670                                               RTLIB::TRUNC_F64,
671                                               RTLIB::TRUNC_F80,
672                                               RTLIB::TRUNC_F128,
673                                               RTLIB::TRUNC_PPCF128));
674 }
675 
676 SDValue DAGTypeLegalizer::SoftenFloatRes_LOAD(SDNode *N) {
677   LoadSDNode *L = cast<LoadSDNode>(N);
678   EVT VT = N->getValueType(0);
679   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
680   SDLoc dl(N);
681 
682   auto MMOFlags =
683       L->getMemOperand()->getFlags() &
684       ~(MachineMemOperand::MOInvariant | MachineMemOperand::MODereferenceable);
685   SDValue NewL;
686   if (L->getExtensionType() == ISD::NON_EXTLOAD) {
687     NewL = DAG.getLoad(L->getAddressingMode(), L->getExtensionType(), NVT, dl,
688                        L->getChain(), L->getBasePtr(), L->getOffset(),
689                        L->getPointerInfo(), NVT, L->getOriginalAlign(),
690                        MMOFlags, L->getAAInfo());
691     // Legalized the chain result - switch anything that used the old chain to
692     // use the new one.
693     ReplaceValueWith(SDValue(N, 1), NewL.getValue(1));
694     return NewL;
695   }
696 
697   // Do a non-extending load followed by FP_EXTEND.
698   NewL = DAG.getLoad(L->getAddressingMode(), ISD::NON_EXTLOAD, L->getMemoryVT(),
699                      dl, L->getChain(), L->getBasePtr(), L->getOffset(),
700                      L->getPointerInfo(), L->getMemoryVT(),
701                      L->getOriginalAlign(), MMOFlags, L->getAAInfo());
702   // Legalized the chain result - switch anything that used the old chain to
703   // use the new one.
704   ReplaceValueWith(SDValue(N, 1), NewL.getValue(1));
705   auto ExtendNode = DAG.getNode(ISD::FP_EXTEND, dl, VT, NewL);
706   return BitConvertToInteger(ExtendNode);
707 }
708 
709 SDValue DAGTypeLegalizer::SoftenFloatRes_SELECT(SDNode *N) {
710   SDValue LHS = GetSoftenedFloat(N->getOperand(1));
711   SDValue RHS = GetSoftenedFloat(N->getOperand(2));
712   return DAG.getSelect(SDLoc(N),
713                        LHS.getValueType(), N->getOperand(0), LHS, RHS);
714 }
715 
716 SDValue DAGTypeLegalizer::SoftenFloatRes_SELECT_CC(SDNode *N) {
717   SDValue LHS = GetSoftenedFloat(N->getOperand(2));
718   SDValue RHS = GetSoftenedFloat(N->getOperand(3));
719   return DAG.getNode(ISD::SELECT_CC, SDLoc(N),
720                      LHS.getValueType(), N->getOperand(0),
721                      N->getOperand(1), LHS, RHS, N->getOperand(4));
722 }
723 
724 SDValue DAGTypeLegalizer::SoftenFloatRes_UNDEF(SDNode *N) {
725   return DAG.getUNDEF(TLI.getTypeToTransformTo(*DAG.getContext(),
726                                                N->getValueType(0)));
727 }
728 
729 SDValue DAGTypeLegalizer::SoftenFloatRes_VAARG(SDNode *N) {
730   SDValue Chain = N->getOperand(0); // Get the chain.
731   SDValue Ptr = N->getOperand(1); // Get the pointer.
732   EVT VT = N->getValueType(0);
733   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
734   SDLoc dl(N);
735 
736   SDValue NewVAARG;
737   NewVAARG = DAG.getVAArg(NVT, dl, Chain, Ptr, N->getOperand(2),
738                           N->getConstantOperandVal(3));
739 
740   // Legalized the chain result - switch anything that used the old chain to
741   // use the new one.
742   if (N != NewVAARG.getValue(1).getNode())
743     ReplaceValueWith(SDValue(N, 1), NewVAARG.getValue(1));
744   return NewVAARG;
745 }
746 
747 SDValue DAGTypeLegalizer::SoftenFloatRes_XINT_TO_FP(SDNode *N) {
748   bool IsStrict = N->isStrictFPOpcode();
749   bool Signed = N->getOpcode() == ISD::SINT_TO_FP ||
750                 N->getOpcode() == ISD::STRICT_SINT_TO_FP;
751   EVT SVT = N->getOperand(IsStrict ? 1 : 0).getValueType();
752   EVT RVT = N->getValueType(0);
753   EVT NVT = EVT();
754   SDLoc dl(N);
755 
756   // If the input is not legal, eg: i1 -> fp, then it needs to be promoted to
757   // a larger type, eg: i8 -> fp.  Even if it is legal, no libcall may exactly
758   // match.  Look for an appropriate libcall.
759   RTLIB::Libcall LC = RTLIB::UNKNOWN_LIBCALL;
760   for (unsigned t = MVT::FIRST_INTEGER_VALUETYPE;
761        t <= MVT::LAST_INTEGER_VALUETYPE && LC == RTLIB::UNKNOWN_LIBCALL; ++t) {
762     NVT = (MVT::SimpleValueType)t;
763     // The source needs to big enough to hold the operand.
764     if (NVT.bitsGE(SVT))
765       LC = Signed ? RTLIB::getSINTTOFP(NVT, RVT):RTLIB::getUINTTOFP (NVT, RVT);
766   }
767   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported XINT_TO_FP!");
768 
769   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
770   // Sign/zero extend the argument if the libcall takes a larger type.
771   SDValue Op = DAG.getNode(Signed ? ISD::SIGN_EXTEND : ISD::ZERO_EXTEND, dl,
772                            NVT, N->getOperand(IsStrict ? 1 : 0));
773   TargetLowering::MakeLibCallOptions CallOptions;
774   CallOptions.setSExt(Signed);
775   CallOptions.setTypeListBeforeSoften(SVT, RVT, true);
776   std::pair<SDValue, SDValue> Tmp =
777       TLI.makeLibCall(DAG, LC, TLI.getTypeToTransformTo(*DAG.getContext(), RVT),
778                       Op, CallOptions, dl, Chain);
779 
780   if (IsStrict)
781     ReplaceValueWith(SDValue(N, 1), Tmp.second);
782   return Tmp.first;
783 }
784 
785 SDValue DAGTypeLegalizer::SoftenFloatRes_VECREDUCE(SDNode *N) {
786   // Expand and soften recursively.
787   ReplaceValueWith(SDValue(N, 0), TLI.expandVecReduce(N, DAG));
788   return SDValue();
789 }
790 
791 SDValue DAGTypeLegalizer::SoftenFloatRes_VECREDUCE_SEQ(SDNode *N) {
792   ReplaceValueWith(SDValue(N, 0), TLI.expandVecReduceSeq(N, DAG));
793   return SDValue();
794 }
795 
796 //===----------------------------------------------------------------------===//
797 //  Convert Float Operand to Integer
798 //===----------------------------------------------------------------------===//
799 
800 bool DAGTypeLegalizer::SoftenFloatOperand(SDNode *N, unsigned OpNo) {
801   LLVM_DEBUG(dbgs() << "Soften float operand " << OpNo << ": "; N->dump(&DAG);
802              dbgs() << "\n");
803   SDValue Res = SDValue();
804 
805   switch (N->getOpcode()) {
806   default:
807 #ifndef NDEBUG
808     dbgs() << "SoftenFloatOperand Op #" << OpNo << ": ";
809     N->dump(&DAG); dbgs() << "\n";
810 #endif
811     llvm_unreachable("Do not know how to soften this operator's operand!");
812 
813   case ISD::BITCAST:     Res = SoftenFloatOp_BITCAST(N); break;
814   case ISD::BR_CC:       Res = SoftenFloatOp_BR_CC(N); break;
815   case ISD::FP_TO_FP16:  // Same as FP_ROUND for softening purposes
816   case ISD::STRICT_FP_ROUND:
817   case ISD::FP_ROUND:    Res = SoftenFloatOp_FP_ROUND(N); break;
818   case ISD::STRICT_FP_TO_SINT:
819   case ISD::STRICT_FP_TO_UINT:
820   case ISD::FP_TO_SINT:
821   case ISD::FP_TO_UINT:  Res = SoftenFloatOp_FP_TO_XINT(N); break;
822   case ISD::FP_TO_SINT_SAT:
823   case ISD::FP_TO_UINT_SAT:
824                          Res = SoftenFloatOp_FP_TO_XINT_SAT(N); break;
825   case ISD::STRICT_LROUND:
826   case ISD::LROUND:      Res = SoftenFloatOp_LROUND(N); break;
827   case ISD::STRICT_LLROUND:
828   case ISD::LLROUND:     Res = SoftenFloatOp_LLROUND(N); break;
829   case ISD::STRICT_LRINT:
830   case ISD::LRINT:       Res = SoftenFloatOp_LRINT(N); break;
831   case ISD::STRICT_LLRINT:
832   case ISD::LLRINT:      Res = SoftenFloatOp_LLRINT(N); break;
833   case ISD::SELECT_CC:   Res = SoftenFloatOp_SELECT_CC(N); break;
834   case ISD::STRICT_FSETCC:
835   case ISD::STRICT_FSETCCS:
836   case ISD::SETCC:       Res = SoftenFloatOp_SETCC(N); break;
837   case ISD::STORE:       Res = SoftenFloatOp_STORE(N, OpNo); break;
838   case ISD::FCOPYSIGN:   Res = SoftenFloatOp_FCOPYSIGN(N); break;
839   }
840 
841   // If the result is null, the sub-method took care of registering results etc.
842   if (!Res.getNode()) return false;
843 
844   // If the result is N, the sub-method updated N in place.  Tell the legalizer
845   // core about this to re-analyze.
846   if (Res.getNode() == N)
847     return true;
848 
849   assert(Res.getValueType() == N->getValueType(0) && N->getNumValues() == 1 &&
850          "Invalid operand softening");
851 
852   ReplaceValueWith(SDValue(N, 0), Res);
853   return false;
854 }
855 
856 SDValue DAGTypeLegalizer::SoftenFloatOp_BITCAST(SDNode *N) {
857   SDValue Op0 = GetSoftenedFloat(N->getOperand(0));
858 
859   return DAG.getNode(ISD::BITCAST, SDLoc(N), N->getValueType(0), Op0);
860 }
861 
862 SDValue DAGTypeLegalizer::SoftenFloatOp_FP_ROUND(SDNode *N) {
863   // We actually deal with the partially-softened FP_TO_FP16 node too, which
864   // returns an i16 so doesn't meet the constraints necessary for FP_ROUND.
865   assert(N->getOpcode() == ISD::FP_ROUND || N->getOpcode() == ISD::FP_TO_FP16 ||
866          N->getOpcode() == ISD::STRICT_FP_ROUND);
867 
868   bool IsStrict = N->isStrictFPOpcode();
869   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
870   EVT SVT = Op.getValueType();
871   EVT RVT = N->getValueType(0);
872   EVT FloatRVT = N->getOpcode() == ISD::FP_TO_FP16 ? MVT::f16 : RVT;
873 
874   RTLIB::Libcall LC = RTLIB::getFPROUND(SVT, FloatRVT);
875   assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported FP_ROUND libcall");
876 
877   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
878   Op = GetSoftenedFloat(Op);
879   TargetLowering::MakeLibCallOptions CallOptions;
880   CallOptions.setTypeListBeforeSoften(SVT, RVT, true);
881   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, RVT, Op,
882                                                     CallOptions, SDLoc(N),
883                                                     Chain);
884   if (IsStrict) {
885     ReplaceValueWith(SDValue(N, 1), Tmp.second);
886     ReplaceValueWith(SDValue(N, 0), Tmp.first);
887     return SDValue();
888   }
889   return Tmp.first;
890 }
891 
892 SDValue DAGTypeLegalizer::SoftenFloatOp_BR_CC(SDNode *N) {
893   SDValue NewLHS = N->getOperand(2), NewRHS = N->getOperand(3);
894   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(1))->get();
895 
896   EVT VT = NewLHS.getValueType();
897   NewLHS = GetSoftenedFloat(NewLHS);
898   NewRHS = GetSoftenedFloat(NewRHS);
899   TLI.softenSetCCOperands(DAG, VT, NewLHS, NewRHS, CCCode, SDLoc(N),
900                           N->getOperand(2), N->getOperand(3));
901 
902   // If softenSetCCOperands returned a scalar, we need to compare the result
903   // against zero to select between true and false values.
904   if (!NewRHS.getNode()) {
905     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
906     CCCode = ISD::SETNE;
907   }
908 
909   // Update N to have the operands specified.
910   return SDValue(DAG.UpdateNodeOperands(N, N->getOperand(0),
911                                 DAG.getCondCode(CCCode), NewLHS, NewRHS,
912                                 N->getOperand(4)),
913                  0);
914 }
915 
916 // Even if the result type is legal, no libcall may exactly match. (e.g. We
917 // don't have FP-i8 conversions) This helper method looks for an appropriate
918 // promoted libcall.
919 static RTLIB::Libcall findFPToIntLibcall(EVT SrcVT, EVT RetVT, EVT &Promoted,
920                                          bool Signed) {
921   RTLIB::Libcall LC = RTLIB::UNKNOWN_LIBCALL;
922   for (unsigned IntVT = MVT::FIRST_INTEGER_VALUETYPE;
923        IntVT <= MVT::LAST_INTEGER_VALUETYPE && LC == RTLIB::UNKNOWN_LIBCALL;
924        ++IntVT) {
925     Promoted = (MVT::SimpleValueType)IntVT;
926     // The type needs to big enough to hold the result.
927     if (Promoted.bitsGE(RetVT))
928       LC = Signed ? RTLIB::getFPTOSINT(SrcVT, Promoted)
929                   : RTLIB::getFPTOUINT(SrcVT, Promoted);
930   }
931   return LC;
932 }
933 
934 SDValue DAGTypeLegalizer::SoftenFloatOp_FP_TO_XINT(SDNode *N) {
935   bool IsStrict = N->isStrictFPOpcode();
936   bool Signed = N->getOpcode() == ISD::FP_TO_SINT ||
937                 N->getOpcode() == ISD::STRICT_FP_TO_SINT;
938 
939   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
940   EVT SVT = Op.getValueType();
941   EVT RVT = N->getValueType(0);
942   EVT NVT = EVT();
943   SDLoc dl(N);
944 
945   // If the result is not legal, eg: fp -> i1, then it needs to be promoted to
946   // a larger type, eg: fp -> i32. Even if it is legal, no libcall may exactly
947   // match, eg. we don't have fp -> i8 conversions.
948   // Look for an appropriate libcall.
949   RTLIB::Libcall LC = findFPToIntLibcall(SVT, RVT, NVT, Signed);
950   assert(LC != RTLIB::UNKNOWN_LIBCALL && NVT.isSimple() &&
951          "Unsupported FP_TO_XINT!");
952 
953   Op = GetSoftenedFloat(Op);
954   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
955   TargetLowering::MakeLibCallOptions CallOptions;
956   CallOptions.setTypeListBeforeSoften(SVT, RVT, true);
957   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
958                                                     CallOptions, dl, Chain);
959 
960   // Truncate the result if the libcall returns a larger type.
961   SDValue Res = DAG.getNode(ISD::TRUNCATE, dl, RVT, Tmp.first);
962 
963   if (!IsStrict)
964     return Res;
965 
966   ReplaceValueWith(SDValue(N, 1), Tmp.second);
967   ReplaceValueWith(SDValue(N, 0), Res);
968   return SDValue();
969 }
970 
971 SDValue DAGTypeLegalizer::SoftenFloatOp_FP_TO_XINT_SAT(SDNode *N) {
972   SDValue Res = TLI.expandFP_TO_INT_SAT(N, DAG);
973   return Res;
974 }
975 
976 SDValue DAGTypeLegalizer::SoftenFloatOp_SELECT_CC(SDNode *N) {
977   SDValue NewLHS = N->getOperand(0), NewRHS = N->getOperand(1);
978   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(4))->get();
979 
980   EVT VT = NewLHS.getValueType();
981   NewLHS = GetSoftenedFloat(NewLHS);
982   NewRHS = GetSoftenedFloat(NewRHS);
983   TLI.softenSetCCOperands(DAG, VT, NewLHS, NewRHS, CCCode, SDLoc(N),
984                           N->getOperand(0), N->getOperand(1));
985 
986   // If softenSetCCOperands returned a scalar, we need to compare the result
987   // against zero to select between true and false values.
988   if (!NewRHS.getNode()) {
989     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
990     CCCode = ISD::SETNE;
991   }
992 
993   // Update N to have the operands specified.
994   return SDValue(DAG.UpdateNodeOperands(N, NewLHS, NewRHS,
995                                 N->getOperand(2), N->getOperand(3),
996                                 DAG.getCondCode(CCCode)),
997                  0);
998 }
999 
1000 SDValue DAGTypeLegalizer::SoftenFloatOp_SETCC(SDNode *N) {
1001   bool IsStrict = N->isStrictFPOpcode();
1002   SDValue Op0 = N->getOperand(IsStrict ? 1 : 0);
1003   SDValue Op1 = N->getOperand(IsStrict ? 2 : 1);
1004   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1005   ISD::CondCode CCCode =
1006       cast<CondCodeSDNode>(N->getOperand(IsStrict ? 3 : 2))->get();
1007 
1008   EVT VT = Op0.getValueType();
1009   SDValue NewLHS = GetSoftenedFloat(Op0);
1010   SDValue NewRHS = GetSoftenedFloat(Op1);
1011   TLI.softenSetCCOperands(DAG, VT, NewLHS, NewRHS, CCCode, SDLoc(N), Op0, Op1,
1012                           Chain, N->getOpcode() == ISD::STRICT_FSETCCS);
1013 
1014   // Update N to have the operands specified.
1015   if (NewRHS.getNode()) {
1016     if (IsStrict)
1017       NewLHS = DAG.getNode(ISD::SETCC, SDLoc(N), N->getValueType(0), NewLHS,
1018                            NewRHS, DAG.getCondCode(CCCode));
1019     else
1020       return SDValue(DAG.UpdateNodeOperands(N, NewLHS, NewRHS,
1021                                             DAG.getCondCode(CCCode)), 0);
1022   }
1023 
1024   // Otherwise, softenSetCCOperands returned a scalar, use it.
1025   assert((NewRHS.getNode() || NewLHS.getValueType() == N->getValueType(0)) &&
1026          "Unexpected setcc expansion!");
1027 
1028   if (IsStrict) {
1029     ReplaceValueWith(SDValue(N, 0), NewLHS);
1030     ReplaceValueWith(SDValue(N, 1), Chain);
1031     return SDValue();
1032   }
1033   return NewLHS;
1034 }
1035 
1036 SDValue DAGTypeLegalizer::SoftenFloatOp_STORE(SDNode *N, unsigned OpNo) {
1037   assert(ISD::isUNINDEXEDStore(N) && "Indexed store during type legalization!");
1038   assert(OpNo == 1 && "Can only soften the stored value!");
1039   StoreSDNode *ST = cast<StoreSDNode>(N);
1040   SDValue Val = ST->getValue();
1041   SDLoc dl(N);
1042 
1043   if (ST->isTruncatingStore())
1044     // Do an FP_ROUND followed by a non-truncating store.
1045     Val = BitConvertToInteger(DAG.getNode(ISD::FP_ROUND, dl, ST->getMemoryVT(),
1046                                           Val, DAG.getIntPtrConstant(0, dl)));
1047   else
1048     Val = GetSoftenedFloat(Val);
1049 
1050   return DAG.getStore(ST->getChain(), dl, Val, ST->getBasePtr(),
1051                       ST->getMemOperand());
1052 }
1053 
1054 SDValue DAGTypeLegalizer::SoftenFloatOp_FCOPYSIGN(SDNode *N) {
1055   SDValue LHS = N->getOperand(0);
1056   SDValue RHS = BitConvertToInteger(N->getOperand(1));
1057   SDLoc dl(N);
1058 
1059   EVT LVT = LHS.getValueType();
1060   EVT ILVT = EVT::getIntegerVT(*DAG.getContext(), LVT.getSizeInBits());
1061   EVT RVT = RHS.getValueType();
1062 
1063   unsigned LSize = LVT.getSizeInBits();
1064   unsigned RSize = RVT.getSizeInBits();
1065 
1066   // Shift right or sign-extend it if the two operands have different types.
1067   int SizeDiff = RSize - LSize;
1068   if (SizeDiff > 0) {
1069     RHS =
1070         DAG.getNode(ISD::SRL, dl, RVT, RHS,
1071                     DAG.getConstant(SizeDiff, dl,
1072                                     TLI.getShiftAmountTy(RHS.getValueType(),
1073                                                          DAG.getDataLayout())));
1074     RHS = DAG.getNode(ISD::TRUNCATE, dl, ILVT, RHS);
1075   } else if (SizeDiff < 0) {
1076     RHS = DAG.getNode(ISD::ANY_EXTEND, dl, LVT, RHS);
1077     RHS =
1078         DAG.getNode(ISD::SHL, dl, ILVT, RHS,
1079                     DAG.getConstant(-SizeDiff, dl,
1080                                     TLI.getShiftAmountTy(RHS.getValueType(),
1081                                                          DAG.getDataLayout())));
1082   }
1083 
1084   RHS = DAG.getBitcast(LVT, RHS);
1085   return DAG.getNode(ISD::FCOPYSIGN, dl, LVT, LHS, RHS);
1086 }
1087 
1088 SDValue DAGTypeLegalizer::SoftenFloatOp_Unary(SDNode *N, RTLIB::Libcall LC) {
1089   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
1090   bool IsStrict = N->isStrictFPOpcode();
1091   unsigned Offset = IsStrict ? 1 : 0;
1092   SDValue Op = GetSoftenedFloat(N->getOperand(0 + Offset));
1093   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1094   TargetLowering::MakeLibCallOptions CallOptions;
1095   EVT OpVT = N->getOperand(0 + Offset).getValueType();
1096   CallOptions.setTypeListBeforeSoften(OpVT, N->getValueType(0), true);
1097   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, NVT, Op,
1098                                                     CallOptions, SDLoc(N),
1099                                                     Chain);
1100   if (IsStrict) {
1101     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1102     ReplaceValueWith(SDValue(N, 0), Tmp.first);
1103     return SDValue();
1104   }
1105 
1106   return Tmp.first;
1107 }
1108 
1109 SDValue DAGTypeLegalizer::SoftenFloatOp_LROUND(SDNode *N) {
1110   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1111   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1112                                              RTLIB::LROUND_F32,
1113                                              RTLIB::LROUND_F64,
1114                                              RTLIB::LROUND_F80,
1115                                              RTLIB::LROUND_F128,
1116                                              RTLIB::LROUND_PPCF128));
1117 }
1118 
1119 SDValue DAGTypeLegalizer::SoftenFloatOp_LLROUND(SDNode *N) {
1120   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1121   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1122                                              RTLIB::LLROUND_F32,
1123                                              RTLIB::LLROUND_F64,
1124                                              RTLIB::LLROUND_F80,
1125                                              RTLIB::LLROUND_F128,
1126                                              RTLIB::LLROUND_PPCF128));
1127 }
1128 
1129 SDValue DAGTypeLegalizer::SoftenFloatOp_LRINT(SDNode *N) {
1130   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1131   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1132                                              RTLIB::LRINT_F32,
1133                                              RTLIB::LRINT_F64,
1134                                              RTLIB::LRINT_F80,
1135                                              RTLIB::LRINT_F128,
1136                                              RTLIB::LRINT_PPCF128));
1137 }
1138 
1139 SDValue DAGTypeLegalizer::SoftenFloatOp_LLRINT(SDNode *N) {
1140   EVT OpVT = N->getOperand(N->isStrictFPOpcode() ? 1 : 0).getValueType();
1141   return SoftenFloatOp_Unary(N, GetFPLibCall(OpVT,
1142                                              RTLIB::LLRINT_F32,
1143                                              RTLIB::LLRINT_F64,
1144                                              RTLIB::LLRINT_F80,
1145                                              RTLIB::LLRINT_F128,
1146                                              RTLIB::LLRINT_PPCF128));
1147 }
1148 
1149 //===----------------------------------------------------------------------===//
1150 //  Float Result Expansion
1151 //===----------------------------------------------------------------------===//
1152 
1153 /// ExpandFloatResult - This method is called when the specified result of the
1154 /// specified node is found to need expansion.  At this point, the node may also
1155 /// have invalid operands or may have other results that need promotion, we just
1156 /// know that (at least) one result needs expansion.
1157 void DAGTypeLegalizer::ExpandFloatResult(SDNode *N, unsigned ResNo) {
1158   LLVM_DEBUG(dbgs() << "Expand float result: "; N->dump(&DAG); dbgs() << "\n");
1159   SDValue Lo, Hi;
1160   Lo = Hi = SDValue();
1161 
1162   // See if the target wants to custom expand this node.
1163   if (CustomLowerNode(N, N->getValueType(ResNo), true))
1164     return;
1165 
1166   switch (N->getOpcode()) {
1167   default:
1168 #ifndef NDEBUG
1169     dbgs() << "ExpandFloatResult #" << ResNo << ": ";
1170     N->dump(&DAG); dbgs() << "\n";
1171 #endif
1172     llvm_unreachable("Do not know how to expand the result of this operator!");
1173 
1174   case ISD::UNDEF:        SplitRes_UNDEF(N, Lo, Hi); break;
1175   case ISD::SELECT:       SplitRes_SELECT(N, Lo, Hi); break;
1176   case ISD::SELECT_CC:    SplitRes_SELECT_CC(N, Lo, Hi); break;
1177 
1178   case ISD::MERGE_VALUES:       ExpandRes_MERGE_VALUES(N, ResNo, Lo, Hi); break;
1179   case ISD::BITCAST:            ExpandRes_BITCAST(N, Lo, Hi); break;
1180   case ISD::BUILD_PAIR:         ExpandRes_BUILD_PAIR(N, Lo, Hi); break;
1181   case ISD::EXTRACT_ELEMENT:    ExpandRes_EXTRACT_ELEMENT(N, Lo, Hi); break;
1182   case ISD::EXTRACT_VECTOR_ELT: ExpandRes_EXTRACT_VECTOR_ELT(N, Lo, Hi); break;
1183   case ISD::VAARG:              ExpandRes_VAARG(N, Lo, Hi); break;
1184 
1185   case ISD::ConstantFP: ExpandFloatRes_ConstantFP(N, Lo, Hi); break;
1186   case ISD::FABS:       ExpandFloatRes_FABS(N, Lo, Hi); break;
1187   case ISD::STRICT_FMINNUM:
1188   case ISD::FMINNUM:    ExpandFloatRes_FMINNUM(N, Lo, Hi); break;
1189   case ISD::STRICT_FMAXNUM:
1190   case ISD::FMAXNUM:    ExpandFloatRes_FMAXNUM(N, Lo, Hi); break;
1191   case ISD::STRICT_FADD:
1192   case ISD::FADD:       ExpandFloatRes_FADD(N, Lo, Hi); break;
1193   case ISD::FCBRT:      ExpandFloatRes_FCBRT(N, Lo, Hi); break;
1194   case ISD::STRICT_FCEIL:
1195   case ISD::FCEIL:      ExpandFloatRes_FCEIL(N, Lo, Hi); break;
1196   case ISD::FCOPYSIGN:  ExpandFloatRes_FCOPYSIGN(N, Lo, Hi); break;
1197   case ISD::STRICT_FCOS:
1198   case ISD::FCOS:       ExpandFloatRes_FCOS(N, Lo, Hi); break;
1199   case ISD::STRICT_FDIV:
1200   case ISD::FDIV:       ExpandFloatRes_FDIV(N, Lo, Hi); break;
1201   case ISD::STRICT_FEXP:
1202   case ISD::FEXP:       ExpandFloatRes_FEXP(N, Lo, Hi); break;
1203   case ISD::STRICT_FEXP2:
1204   case ISD::FEXP2:      ExpandFloatRes_FEXP2(N, Lo, Hi); break;
1205   case ISD::STRICT_FFLOOR:
1206   case ISD::FFLOOR:     ExpandFloatRes_FFLOOR(N, Lo, Hi); break;
1207   case ISD::STRICT_FLOG:
1208   case ISD::FLOG:       ExpandFloatRes_FLOG(N, Lo, Hi); break;
1209   case ISD::STRICT_FLOG2:
1210   case ISD::FLOG2:      ExpandFloatRes_FLOG2(N, Lo, Hi); break;
1211   case ISD::STRICT_FLOG10:
1212   case ISD::FLOG10:     ExpandFloatRes_FLOG10(N, Lo, Hi); break;
1213   case ISD::STRICT_FMA:
1214   case ISD::FMA:        ExpandFloatRes_FMA(N, Lo, Hi); break;
1215   case ISD::STRICT_FMUL:
1216   case ISD::FMUL:       ExpandFloatRes_FMUL(N, Lo, Hi); break;
1217   case ISD::STRICT_FNEARBYINT:
1218   case ISD::FNEARBYINT: ExpandFloatRes_FNEARBYINT(N, Lo, Hi); break;
1219   case ISD::FNEG:       ExpandFloatRes_FNEG(N, Lo, Hi); break;
1220   case ISD::STRICT_FP_EXTEND:
1221   case ISD::FP_EXTEND:  ExpandFloatRes_FP_EXTEND(N, Lo, Hi); break;
1222   case ISD::STRICT_FPOW:
1223   case ISD::FPOW:       ExpandFloatRes_FPOW(N, Lo, Hi); break;
1224   case ISD::STRICT_FPOWI:
1225   case ISD::FPOWI:      ExpandFloatRes_FPOWI(N, Lo, Hi); break;
1226   case ISD::FREEZE:     ExpandFloatRes_FREEZE(N, Lo, Hi); break;
1227   case ISD::STRICT_FRINT:
1228   case ISD::FRINT:      ExpandFloatRes_FRINT(N, Lo, Hi); break;
1229   case ISD::STRICT_FROUND:
1230   case ISD::FROUND:     ExpandFloatRes_FROUND(N, Lo, Hi); break;
1231   case ISD::STRICT_FROUNDEVEN:
1232   case ISD::FROUNDEVEN: ExpandFloatRes_FROUNDEVEN(N, Lo, Hi); break;
1233   case ISD::STRICT_FSIN:
1234   case ISD::FSIN:       ExpandFloatRes_FSIN(N, Lo, Hi); break;
1235   case ISD::STRICT_FSQRT:
1236   case ISD::FSQRT:      ExpandFloatRes_FSQRT(N, Lo, Hi); break;
1237   case ISD::STRICT_FSUB:
1238   case ISD::FSUB:       ExpandFloatRes_FSUB(N, Lo, Hi); break;
1239   case ISD::STRICT_FTRUNC:
1240   case ISD::FTRUNC:     ExpandFloatRes_FTRUNC(N, Lo, Hi); break;
1241   case ISD::LOAD:       ExpandFloatRes_LOAD(N, Lo, Hi); break;
1242   case ISD::STRICT_SINT_TO_FP:
1243   case ISD::STRICT_UINT_TO_FP:
1244   case ISD::SINT_TO_FP:
1245   case ISD::UINT_TO_FP: ExpandFloatRes_XINT_TO_FP(N, Lo, Hi); break;
1246   case ISD::STRICT_FREM:
1247   case ISD::FREM:       ExpandFloatRes_FREM(N, Lo, Hi); break;
1248   }
1249 
1250   // If Lo/Hi is null, the sub-method took care of registering results etc.
1251   if (Lo.getNode())
1252     SetExpandedFloat(SDValue(N, ResNo), Lo, Hi);
1253 }
1254 
1255 void DAGTypeLegalizer::ExpandFloatRes_ConstantFP(SDNode *N, SDValue &Lo,
1256                                                  SDValue &Hi) {
1257   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
1258   assert(NVT.getSizeInBits() == 64 &&
1259          "Do not know how to expand this float constant!");
1260   APInt C = cast<ConstantFPSDNode>(N)->getValueAPF().bitcastToAPInt();
1261   SDLoc dl(N);
1262   Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1263                                  APInt(64, C.getRawData()[1])),
1264                          dl, NVT);
1265   Hi = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1266                                  APInt(64, C.getRawData()[0])),
1267                          dl, NVT);
1268 }
1269 
1270 void DAGTypeLegalizer::ExpandFloatRes_Unary(SDNode *N, RTLIB::Libcall LC,
1271                                             SDValue &Lo, SDValue &Hi) {
1272   bool IsStrict = N->isStrictFPOpcode();
1273   unsigned Offset = IsStrict ? 1 : 0;
1274   SDValue Op = N->getOperand(0 + Offset);
1275   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1276   TargetLowering::MakeLibCallOptions CallOptions;
1277   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, N->getValueType(0),
1278                                                     Op, CallOptions, SDLoc(N),
1279                                                     Chain);
1280   if (IsStrict)
1281     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1282   GetPairElements(Tmp.first, Lo, Hi);
1283 }
1284 
1285 void DAGTypeLegalizer::ExpandFloatRes_Binary(SDNode *N, RTLIB::Libcall LC,
1286                                              SDValue &Lo, SDValue &Hi) {
1287   bool IsStrict = N->isStrictFPOpcode();
1288   unsigned Offset = IsStrict ? 1 : 0;
1289   SDValue Ops[] = { N->getOperand(0 + Offset), N->getOperand(1 + Offset) };
1290   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1291   TargetLowering::MakeLibCallOptions CallOptions;
1292   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, LC, N->getValueType(0),
1293                                                     Ops, CallOptions, SDLoc(N),
1294                                                     Chain);
1295   if (IsStrict)
1296     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1297   GetPairElements(Tmp.first, Lo, Hi);
1298 }
1299 
1300 void DAGTypeLegalizer::ExpandFloatRes_FABS(SDNode *N, SDValue &Lo,
1301                                            SDValue &Hi) {
1302   assert(N->getValueType(0) == MVT::ppcf128 &&
1303          "Logic only correct for ppcf128!");
1304   SDLoc dl(N);
1305   SDValue Tmp;
1306   GetExpandedFloat(N->getOperand(0), Lo, Tmp);
1307   Hi = DAG.getNode(ISD::FABS, dl, Tmp.getValueType(), Tmp);
1308   // Lo = Hi==fabs(Hi) ? Lo : -Lo;
1309   Lo = DAG.getSelectCC(dl, Tmp, Hi, Lo,
1310                    DAG.getNode(ISD::FNEG, dl, Lo.getValueType(), Lo),
1311                    ISD::SETEQ);
1312 }
1313 
1314 void DAGTypeLegalizer::ExpandFloatRes_FMINNUM(SDNode *N, SDValue &Lo,
1315                                               SDValue &Hi) {
1316   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1317                                        RTLIB::FMIN_F32, RTLIB::FMIN_F64,
1318                                        RTLIB::FMIN_F80, RTLIB::FMIN_F128,
1319                                        RTLIB::FMIN_PPCF128), Lo, Hi);
1320 }
1321 
1322 void DAGTypeLegalizer::ExpandFloatRes_FMAXNUM(SDNode *N, SDValue &Lo,
1323                                               SDValue &Hi) {
1324   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1325                                         RTLIB::FMAX_F32, RTLIB::FMAX_F64,
1326                                         RTLIB::FMAX_F80, RTLIB::FMAX_F128,
1327                                         RTLIB::FMAX_PPCF128), Lo, Hi);
1328 }
1329 
1330 void DAGTypeLegalizer::ExpandFloatRes_FADD(SDNode *N, SDValue &Lo,
1331                                            SDValue &Hi) {
1332   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1333                                         RTLIB::ADD_F32, RTLIB::ADD_F64,
1334                                         RTLIB::ADD_F80, RTLIB::ADD_F128,
1335                                         RTLIB::ADD_PPCF128), Lo, Hi);
1336 }
1337 
1338 void DAGTypeLegalizer::ExpandFloatRes_FCBRT(SDNode *N, SDValue &Lo,
1339                                             SDValue &Hi) {
1340   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0), RTLIB::CBRT_F32,
1341                                        RTLIB::CBRT_F64, RTLIB::CBRT_F80,
1342                                        RTLIB::CBRT_F128,
1343                                        RTLIB::CBRT_PPCF128), Lo, Hi);
1344 }
1345 
1346 void DAGTypeLegalizer::ExpandFloatRes_FCEIL(SDNode *N,
1347                                             SDValue &Lo, SDValue &Hi) {
1348   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1349                                        RTLIB::CEIL_F32, RTLIB::CEIL_F64,
1350                                        RTLIB::CEIL_F80, RTLIB::CEIL_F128,
1351                                        RTLIB::CEIL_PPCF128), Lo, Hi);
1352 }
1353 
1354 void DAGTypeLegalizer::ExpandFloatRes_FCOPYSIGN(SDNode *N,
1355                                                 SDValue &Lo, SDValue &Hi) {
1356   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1357                                         RTLIB::COPYSIGN_F32,
1358                                         RTLIB::COPYSIGN_F64,
1359                                         RTLIB::COPYSIGN_F80,
1360                                         RTLIB::COPYSIGN_F128,
1361                                         RTLIB::COPYSIGN_PPCF128), Lo, Hi);
1362 }
1363 
1364 void DAGTypeLegalizer::ExpandFloatRes_FCOS(SDNode *N,
1365                                            SDValue &Lo, SDValue &Hi) {
1366   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1367                                        RTLIB::COS_F32, RTLIB::COS_F64,
1368                                        RTLIB::COS_F80, RTLIB::COS_F128,
1369                                        RTLIB::COS_PPCF128), Lo, Hi);
1370 }
1371 
1372 void DAGTypeLegalizer::ExpandFloatRes_FDIV(SDNode *N, SDValue &Lo,
1373                                            SDValue &Hi) {
1374   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1375                                         RTLIB::DIV_F32,
1376                                         RTLIB::DIV_F64,
1377                                         RTLIB::DIV_F80,
1378                                         RTLIB::DIV_F128,
1379                                         RTLIB::DIV_PPCF128), Lo, Hi);
1380 }
1381 
1382 void DAGTypeLegalizer::ExpandFloatRes_FEXP(SDNode *N,
1383                                            SDValue &Lo, SDValue &Hi) {
1384   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1385                                        RTLIB::EXP_F32, RTLIB::EXP_F64,
1386                                        RTLIB::EXP_F80, RTLIB::EXP_F128,
1387                                        RTLIB::EXP_PPCF128), Lo, Hi);
1388 }
1389 
1390 void DAGTypeLegalizer::ExpandFloatRes_FEXP2(SDNode *N,
1391                                             SDValue &Lo, SDValue &Hi) {
1392   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1393                                        RTLIB::EXP2_F32, RTLIB::EXP2_F64,
1394                                        RTLIB::EXP2_F80, RTLIB::EXP2_F128,
1395                                        RTLIB::EXP2_PPCF128), Lo, Hi);
1396 }
1397 
1398 void DAGTypeLegalizer::ExpandFloatRes_FFLOOR(SDNode *N,
1399                                              SDValue &Lo, SDValue &Hi) {
1400   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1401                                        RTLIB::FLOOR_F32, RTLIB::FLOOR_F64,
1402                                        RTLIB::FLOOR_F80, RTLIB::FLOOR_F128,
1403                                        RTLIB::FLOOR_PPCF128), Lo, Hi);
1404 }
1405 
1406 void DAGTypeLegalizer::ExpandFloatRes_FLOG(SDNode *N,
1407                                            SDValue &Lo, SDValue &Hi) {
1408   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1409                                        RTLIB::LOG_F32, RTLIB::LOG_F64,
1410                                        RTLIB::LOG_F80, RTLIB::LOG_F128,
1411                                        RTLIB::LOG_PPCF128), Lo, Hi);
1412 }
1413 
1414 void DAGTypeLegalizer::ExpandFloatRes_FLOG2(SDNode *N,
1415                                             SDValue &Lo, SDValue &Hi) {
1416   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1417                                        RTLIB::LOG2_F32, RTLIB::LOG2_F64,
1418                                        RTLIB::LOG2_F80, RTLIB::LOG2_F128,
1419                                        RTLIB::LOG2_PPCF128), Lo, Hi);
1420 }
1421 
1422 void DAGTypeLegalizer::ExpandFloatRes_FLOG10(SDNode *N,
1423                                              SDValue &Lo, SDValue &Hi) {
1424   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1425                                        RTLIB::LOG10_F32, RTLIB::LOG10_F64,
1426                                        RTLIB::LOG10_F80, RTLIB::LOG10_F128,
1427                                        RTLIB::LOG10_PPCF128), Lo, Hi);
1428 }
1429 
1430 void DAGTypeLegalizer::ExpandFloatRes_FMA(SDNode *N, SDValue &Lo,
1431                                           SDValue &Hi) {
1432   bool IsStrict = N->isStrictFPOpcode();
1433   unsigned Offset = IsStrict ? 1 : 0;
1434   SDValue Ops[3] = { N->getOperand(0 + Offset), N->getOperand(1 + Offset),
1435                      N->getOperand(2 + Offset) };
1436   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1437   TargetLowering::MakeLibCallOptions CallOptions;
1438   std::pair<SDValue, SDValue> Tmp = TLI.makeLibCall(DAG, GetFPLibCall(N->getValueType(0),
1439                                                    RTLIB::FMA_F32,
1440                                                    RTLIB::FMA_F64,
1441                                                    RTLIB::FMA_F80,
1442                                                    RTLIB::FMA_F128,
1443                                                    RTLIB::FMA_PPCF128),
1444                                  N->getValueType(0), Ops, CallOptions,
1445                                  SDLoc(N), Chain);
1446   if (IsStrict)
1447     ReplaceValueWith(SDValue(N, 1), Tmp.second);
1448   GetPairElements(Tmp.first, Lo, Hi);
1449 }
1450 
1451 void DAGTypeLegalizer::ExpandFloatRes_FMUL(SDNode *N, SDValue &Lo,
1452                                            SDValue &Hi) {
1453   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1454                                                    RTLIB::MUL_F32,
1455                                                    RTLIB::MUL_F64,
1456                                                    RTLIB::MUL_F80,
1457                                                    RTLIB::MUL_F128,
1458                                                    RTLIB::MUL_PPCF128), Lo, Hi);
1459 }
1460 
1461 void DAGTypeLegalizer::ExpandFloatRes_FNEARBYINT(SDNode *N,
1462                                                  SDValue &Lo, SDValue &Hi) {
1463   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1464                                        RTLIB::NEARBYINT_F32,
1465                                        RTLIB::NEARBYINT_F64,
1466                                        RTLIB::NEARBYINT_F80,
1467                                        RTLIB::NEARBYINT_F128,
1468                                        RTLIB::NEARBYINT_PPCF128), Lo, Hi);
1469 }
1470 
1471 void DAGTypeLegalizer::ExpandFloatRes_FNEG(SDNode *N, SDValue &Lo,
1472                                            SDValue &Hi) {
1473   SDLoc dl(N);
1474   GetExpandedFloat(N->getOperand(0), Lo, Hi);
1475   Lo = DAG.getNode(ISD::FNEG, dl, Lo.getValueType(), Lo);
1476   Hi = DAG.getNode(ISD::FNEG, dl, Hi.getValueType(), Hi);
1477 }
1478 
1479 void DAGTypeLegalizer::ExpandFloatRes_FP_EXTEND(SDNode *N, SDValue &Lo,
1480                                                 SDValue &Hi) {
1481   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
1482   SDLoc dl(N);
1483   bool IsStrict = N->isStrictFPOpcode();
1484 
1485   SDValue Chain;
1486   if (IsStrict) {
1487     // If the expanded type is the same as the input type, just bypass the node.
1488     if (NVT == N->getOperand(1).getValueType()) {
1489       Hi = N->getOperand(1);
1490       Chain = N->getOperand(0);
1491     } else {
1492       // Other we need to extend.
1493       Hi = DAG.getNode(ISD::STRICT_FP_EXTEND, dl, { NVT, MVT::Other },
1494                        { N->getOperand(0), N->getOperand(1) });
1495       Chain = Hi.getValue(1);
1496     }
1497   } else {
1498     Hi = DAG.getNode(ISD::FP_EXTEND, dl, NVT, N->getOperand(0));
1499   }
1500 
1501   Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1502                                  APInt(NVT.getSizeInBits(), 0)), dl, NVT);
1503 
1504   if (IsStrict)
1505     ReplaceValueWith(SDValue(N, 1), Chain);
1506 }
1507 
1508 void DAGTypeLegalizer::ExpandFloatRes_FPOW(SDNode *N,
1509                                            SDValue &Lo, SDValue &Hi) {
1510   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1511                                         RTLIB::POW_F32, RTLIB::POW_F64,
1512                                         RTLIB::POW_F80, RTLIB::POW_F128,
1513                                         RTLIB::POW_PPCF128), Lo, Hi);
1514 }
1515 
1516 void DAGTypeLegalizer::ExpandFloatRes_FPOWI(SDNode *N,
1517                                             SDValue &Lo, SDValue &Hi) {
1518   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1519                                         RTLIB::POWI_F32, RTLIB::POWI_F64,
1520                                         RTLIB::POWI_F80, RTLIB::POWI_F128,
1521                                         RTLIB::POWI_PPCF128), Lo, Hi);
1522 }
1523 
1524 void DAGTypeLegalizer::ExpandFloatRes_FREEZE(SDNode *N,
1525                                              SDValue &Lo, SDValue &Hi) {
1526   assert(N->getValueType(0) == MVT::ppcf128 &&
1527          "Logic only correct for ppcf128!");
1528 
1529   SDLoc dl(N);
1530   GetExpandedFloat(N->getOperand(0), Lo, Hi);
1531   Lo = DAG.getNode(ISD::FREEZE, dl, Lo.getValueType(), Lo);
1532   Hi = DAG.getNode(ISD::FREEZE, dl, Hi.getValueType(), Hi);
1533 }
1534 
1535 void DAGTypeLegalizer::ExpandFloatRes_FREM(SDNode *N,
1536                                            SDValue &Lo, SDValue &Hi) {
1537   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1538                                         RTLIB::REM_F32, RTLIB::REM_F64,
1539                                         RTLIB::REM_F80, RTLIB::REM_F128,
1540                                         RTLIB::REM_PPCF128), Lo, Hi);
1541 }
1542 
1543 void DAGTypeLegalizer::ExpandFloatRes_FRINT(SDNode *N,
1544                                             SDValue &Lo, SDValue &Hi) {
1545   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1546                                        RTLIB::RINT_F32, RTLIB::RINT_F64,
1547                                        RTLIB::RINT_F80, RTLIB::RINT_F128,
1548                                        RTLIB::RINT_PPCF128), Lo, Hi);
1549 }
1550 
1551 void DAGTypeLegalizer::ExpandFloatRes_FROUND(SDNode *N,
1552                                              SDValue &Lo, SDValue &Hi) {
1553   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1554                                        RTLIB::ROUND_F32,
1555                                        RTLIB::ROUND_F64,
1556                                        RTLIB::ROUND_F80,
1557                                        RTLIB::ROUND_F128,
1558                                        RTLIB::ROUND_PPCF128), Lo, Hi);
1559 }
1560 
1561 void DAGTypeLegalizer::ExpandFloatRes_FROUNDEVEN(SDNode *N,
1562                                              SDValue &Lo, SDValue &Hi) {
1563   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1564                                        RTLIB::ROUNDEVEN_F32,
1565                                        RTLIB::ROUNDEVEN_F64,
1566                                        RTLIB::ROUNDEVEN_F80,
1567                                        RTLIB::ROUNDEVEN_F128,
1568                                        RTLIB::ROUNDEVEN_PPCF128), Lo, Hi);
1569 }
1570 
1571 void DAGTypeLegalizer::ExpandFloatRes_FSIN(SDNode *N,
1572                                            SDValue &Lo, SDValue &Hi) {
1573   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1574                                        RTLIB::SIN_F32, RTLIB::SIN_F64,
1575                                        RTLIB::SIN_F80, RTLIB::SIN_F128,
1576                                        RTLIB::SIN_PPCF128), Lo, Hi);
1577 }
1578 
1579 void DAGTypeLegalizer::ExpandFloatRes_FSQRT(SDNode *N,
1580                                             SDValue &Lo, SDValue &Hi) {
1581   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1582                                        RTLIB::SQRT_F32, RTLIB::SQRT_F64,
1583                                        RTLIB::SQRT_F80, RTLIB::SQRT_F128,
1584                                        RTLIB::SQRT_PPCF128), Lo, Hi);
1585 }
1586 
1587 void DAGTypeLegalizer::ExpandFloatRes_FSUB(SDNode *N, SDValue &Lo,
1588                                            SDValue &Hi) {
1589   ExpandFloatRes_Binary(N, GetFPLibCall(N->getValueType(0),
1590                                         RTLIB::SUB_F32,
1591                                         RTLIB::SUB_F64,
1592                                         RTLIB::SUB_F80,
1593                                         RTLIB::SUB_F128,
1594                                         RTLIB::SUB_PPCF128), Lo, Hi);
1595 }
1596 
1597 void DAGTypeLegalizer::ExpandFloatRes_FTRUNC(SDNode *N,
1598                                              SDValue &Lo, SDValue &Hi) {
1599   ExpandFloatRes_Unary(N, GetFPLibCall(N->getValueType(0),
1600                                        RTLIB::TRUNC_F32, RTLIB::TRUNC_F64,
1601                                        RTLIB::TRUNC_F80, RTLIB::TRUNC_F128,
1602                                        RTLIB::TRUNC_PPCF128), Lo, Hi);
1603 }
1604 
1605 void DAGTypeLegalizer::ExpandFloatRes_LOAD(SDNode *N, SDValue &Lo,
1606                                            SDValue &Hi) {
1607   if (ISD::isNormalLoad(N)) {
1608     ExpandRes_NormalLoad(N, Lo, Hi);
1609     return;
1610   }
1611 
1612   assert(ISD::isUNINDEXEDLoad(N) && "Indexed load during type legalization!");
1613   LoadSDNode *LD = cast<LoadSDNode>(N);
1614   SDValue Chain = LD->getChain();
1615   SDValue Ptr = LD->getBasePtr();
1616   SDLoc dl(N);
1617 
1618   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), LD->getValueType(0));
1619   assert(NVT.isByteSized() && "Expanded type not byte sized!");
1620   assert(LD->getMemoryVT().bitsLE(NVT) && "Float type not round?");
1621 
1622   Hi = DAG.getExtLoad(LD->getExtensionType(), dl, NVT, Chain, Ptr,
1623                       LD->getMemoryVT(), LD->getMemOperand());
1624 
1625   // Remember the chain.
1626   Chain = Hi.getValue(1);
1627 
1628   // The low part is zero.
1629   Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1630                                  APInt(NVT.getSizeInBits(), 0)), dl, NVT);
1631 
1632   // Modified the chain - switch anything that used the old chain to use the
1633   // new one.
1634   ReplaceValueWith(SDValue(LD, 1), Chain);
1635 }
1636 
1637 void DAGTypeLegalizer::ExpandFloatRes_XINT_TO_FP(SDNode *N, SDValue &Lo,
1638                                                  SDValue &Hi) {
1639   assert(N->getValueType(0) == MVT::ppcf128 && "Unsupported XINT_TO_FP!");
1640   EVT VT = N->getValueType(0);
1641   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
1642   bool Strict = N->isStrictFPOpcode();
1643   SDValue Src = N->getOperand(Strict ? 1 : 0);
1644   EVT SrcVT = Src.getValueType();
1645   bool isSigned = N->getOpcode() == ISD::SINT_TO_FP ||
1646                   N->getOpcode() == ISD::STRICT_SINT_TO_FP;
1647   SDLoc dl(N);
1648   SDValue Chain = Strict ? N->getOperand(0) : DAG.getEntryNode();
1649 
1650   // TODO: Any other flags to propagate?
1651   SDNodeFlags Flags;
1652   Flags.setNoFPExcept(N->getFlags().hasNoFPExcept());
1653 
1654   // First do an SINT_TO_FP, whether the original was signed or unsigned.
1655   // When promoting partial word types to i32 we must honor the signedness,
1656   // though.
1657   if (SrcVT.bitsLE(MVT::i32)) {
1658     // The integer can be represented exactly in an f64.
1659     Lo = DAG.getConstantFP(APFloat(DAG.EVTToAPFloatSemantics(NVT),
1660                                    APInt(NVT.getSizeInBits(), 0)), dl, NVT);
1661     if (Strict) {
1662       Hi = DAG.getNode(N->getOpcode(), dl, DAG.getVTList(NVT, MVT::Other),
1663                        {Chain, Src}, Flags);
1664       Chain = Hi.getValue(1);
1665     } else
1666       Hi = DAG.getNode(N->getOpcode(), dl, NVT, Src);
1667   } else {
1668     RTLIB::Libcall LC = RTLIB::UNKNOWN_LIBCALL;
1669     if (SrcVT.bitsLE(MVT::i64)) {
1670       Src = DAG.getNode(isSigned ? ISD::SIGN_EXTEND : ISD::ZERO_EXTEND, dl,
1671                         MVT::i64, Src);
1672       LC = RTLIB::SINTTOFP_I64_PPCF128;
1673     } else if (SrcVT.bitsLE(MVT::i128)) {
1674       Src = DAG.getNode(ISD::SIGN_EXTEND, dl, MVT::i128, Src);
1675       LC = RTLIB::SINTTOFP_I128_PPCF128;
1676     }
1677     assert(LC != RTLIB::UNKNOWN_LIBCALL && "Unsupported XINT_TO_FP!");
1678 
1679     TargetLowering::MakeLibCallOptions CallOptions;
1680     CallOptions.setSExt(true);
1681     std::pair<SDValue, SDValue> Tmp =
1682         TLI.makeLibCall(DAG, LC, VT, Src, CallOptions, dl, Chain);
1683     if (Strict)
1684       Chain = Tmp.second;
1685     GetPairElements(Tmp.first, Lo, Hi);
1686   }
1687 
1688   // No need to complement for unsigned 32-bit integers
1689   if (isSigned || SrcVT.bitsLE(MVT::i32)) {
1690     if (Strict)
1691       ReplaceValueWith(SDValue(N, 1), Chain);
1692 
1693     return;
1694   }
1695 
1696   // Unsigned - fix up the SINT_TO_FP value just calculated.
1697   // FIXME: For unsigned i128 to ppc_fp128 conversion, we need to carefully
1698   // keep semantics correctness if the integer is not exactly representable
1699   // here. See ExpandLegalINT_TO_FP.
1700   Hi = DAG.getNode(ISD::BUILD_PAIR, dl, VT, Lo, Hi);
1701   SrcVT = Src.getValueType();
1702 
1703   // x>=0 ? (ppcf128)(iN)x : (ppcf128)(iN)x + 2^N; N=32,64,128.
1704   static const uint64_t TwoE32[]  = { 0x41f0000000000000LL, 0 };
1705   static const uint64_t TwoE64[]  = { 0x43f0000000000000LL, 0 };
1706   static const uint64_t TwoE128[] = { 0x47f0000000000000LL, 0 };
1707   ArrayRef<uint64_t> Parts;
1708 
1709   switch (SrcVT.getSimpleVT().SimpleTy) {
1710   default:
1711     llvm_unreachable("Unsupported UINT_TO_FP!");
1712   case MVT::i32:
1713     Parts = TwoE32;
1714     break;
1715   case MVT::i64:
1716     Parts = TwoE64;
1717     break;
1718   case MVT::i128:
1719     Parts = TwoE128;
1720     break;
1721   }
1722 
1723   // TODO: Are there other fast-math-flags to propagate to this FADD?
1724   SDValue NewLo = DAG.getConstantFP(
1725       APFloat(APFloat::PPCDoubleDouble(), APInt(128, Parts)), dl, MVT::ppcf128);
1726   if (Strict) {
1727     Lo = DAG.getNode(ISD::STRICT_FADD, dl, DAG.getVTList(VT, MVT::Other),
1728                      {Chain, Hi, NewLo}, Flags);
1729     Chain = Lo.getValue(1);
1730     ReplaceValueWith(SDValue(N, 1), Chain);
1731   } else
1732     Lo = DAG.getNode(ISD::FADD, dl, VT, Hi, NewLo);
1733   Lo = DAG.getSelectCC(dl, Src, DAG.getConstant(0, dl, SrcVT),
1734                        Lo, Hi, ISD::SETLT);
1735   GetPairElements(Lo, Lo, Hi);
1736 }
1737 
1738 
1739 //===----------------------------------------------------------------------===//
1740 //  Float Operand Expansion
1741 //===----------------------------------------------------------------------===//
1742 
1743 /// ExpandFloatOperand - This method is called when the specified operand of the
1744 /// specified node is found to need expansion.  At this point, all of the result
1745 /// types of the node are known to be legal, but other operands of the node may
1746 /// need promotion or expansion as well as the specified one.
1747 bool DAGTypeLegalizer::ExpandFloatOperand(SDNode *N, unsigned OpNo) {
1748   LLVM_DEBUG(dbgs() << "Expand float operand: "; N->dump(&DAG); dbgs() << "\n");
1749   SDValue Res = SDValue();
1750 
1751   // See if the target wants to custom expand this node.
1752   if (CustomLowerNode(N, N->getOperand(OpNo).getValueType(), false))
1753     return false;
1754 
1755   switch (N->getOpcode()) {
1756   default:
1757 #ifndef NDEBUG
1758     dbgs() << "ExpandFloatOperand Op #" << OpNo << ": ";
1759     N->dump(&DAG); dbgs() << "\n";
1760 #endif
1761     llvm_unreachable("Do not know how to expand this operator's operand!");
1762 
1763   case ISD::BITCAST:         Res = ExpandOp_BITCAST(N); break;
1764   case ISD::BUILD_VECTOR:    Res = ExpandOp_BUILD_VECTOR(N); break;
1765   case ISD::EXTRACT_ELEMENT: Res = ExpandOp_EXTRACT_ELEMENT(N); break;
1766 
1767   case ISD::BR_CC:      Res = ExpandFloatOp_BR_CC(N); break;
1768   case ISD::FCOPYSIGN:  Res = ExpandFloatOp_FCOPYSIGN(N); break;
1769   case ISD::STRICT_FP_ROUND:
1770   case ISD::FP_ROUND:   Res = ExpandFloatOp_FP_ROUND(N); break;
1771   case ISD::STRICT_FP_TO_SINT:
1772   case ISD::STRICT_FP_TO_UINT:
1773   case ISD::FP_TO_SINT:
1774   case ISD::FP_TO_UINT: Res = ExpandFloatOp_FP_TO_XINT(N); break;
1775   case ISD::LROUND:     Res = ExpandFloatOp_LROUND(N); break;
1776   case ISD::LLROUND:    Res = ExpandFloatOp_LLROUND(N); break;
1777   case ISD::LRINT:      Res = ExpandFloatOp_LRINT(N); break;
1778   case ISD::LLRINT:     Res = ExpandFloatOp_LLRINT(N); break;
1779   case ISD::SELECT_CC:  Res = ExpandFloatOp_SELECT_CC(N); break;
1780   case ISD::STRICT_FSETCC:
1781   case ISD::STRICT_FSETCCS:
1782   case ISD::SETCC:      Res = ExpandFloatOp_SETCC(N); break;
1783   case ISD::STORE:      Res = ExpandFloatOp_STORE(cast<StoreSDNode>(N),
1784                                                   OpNo); break;
1785   }
1786 
1787   // If the result is null, the sub-method took care of registering results etc.
1788   if (!Res.getNode()) return false;
1789 
1790   // If the result is N, the sub-method updated N in place.  Tell the legalizer
1791   // core about this.
1792   if (Res.getNode() == N)
1793     return true;
1794 
1795   assert(Res.getValueType() == N->getValueType(0) && N->getNumValues() == 1 &&
1796          "Invalid operand expansion");
1797 
1798   ReplaceValueWith(SDValue(N, 0), Res);
1799   return false;
1800 }
1801 
1802 /// FloatExpandSetCCOperands - Expand the operands of a comparison.  This code
1803 /// is shared among BR_CC, SELECT_CC, and SETCC handlers.
1804 void DAGTypeLegalizer::FloatExpandSetCCOperands(SDValue &NewLHS,
1805                                                 SDValue &NewRHS,
1806                                                 ISD::CondCode &CCCode,
1807                                                 const SDLoc &dl, SDValue &Chain,
1808                                                 bool IsSignaling) {
1809   SDValue LHSLo, LHSHi, RHSLo, RHSHi;
1810   GetExpandedFloat(NewLHS, LHSLo, LHSHi);
1811   GetExpandedFloat(NewRHS, RHSLo, RHSHi);
1812 
1813   assert(NewLHS.getValueType() == MVT::ppcf128 && "Unsupported setcc type!");
1814 
1815   // FIXME:  This generated code sucks.  We want to generate
1816   //         FCMPU crN, hi1, hi2
1817   //         BNE crN, L:
1818   //         FCMPU crN, lo1, lo2
1819   // The following can be improved, but not that much.
1820   SDValue Tmp1, Tmp2, Tmp3, OutputChain;
1821   Tmp1 = DAG.getSetCC(dl, getSetCCResultType(LHSHi.getValueType()), LHSHi,
1822                       RHSHi, ISD::SETOEQ, Chain, IsSignaling);
1823   OutputChain = Tmp1->getNumValues() > 1 ? Tmp1.getValue(1) : SDValue();
1824   Tmp2 = DAG.getSetCC(dl, getSetCCResultType(LHSLo.getValueType()), LHSLo,
1825                       RHSLo, CCCode, OutputChain, IsSignaling);
1826   OutputChain = Tmp2->getNumValues() > 1 ? Tmp2.getValue(1) : SDValue();
1827   Tmp3 = DAG.getNode(ISD::AND, dl, Tmp1.getValueType(), Tmp1, Tmp2);
1828   Tmp1 =
1829       DAG.getSetCC(dl, getSetCCResultType(LHSHi.getValueType()), LHSHi, RHSHi,
1830                    ISD::SETUNE, OutputChain, IsSignaling);
1831   OutputChain = Tmp1->getNumValues() > 1 ? Tmp1.getValue(1) : SDValue();
1832   Tmp2 = DAG.getSetCC(dl, getSetCCResultType(LHSHi.getValueType()), LHSHi,
1833                       RHSHi, CCCode, OutputChain, IsSignaling);
1834   OutputChain = Tmp2->getNumValues() > 1 ? Tmp2.getValue(1) : SDValue();
1835   Tmp1 = DAG.getNode(ISD::AND, dl, Tmp1.getValueType(), Tmp1, Tmp2);
1836   NewLHS = DAG.getNode(ISD::OR, dl, Tmp1.getValueType(), Tmp1, Tmp3);
1837   NewRHS = SDValue();   // LHS is the result, not a compare.
1838   Chain = OutputChain;
1839 }
1840 
1841 SDValue DAGTypeLegalizer::ExpandFloatOp_BR_CC(SDNode *N) {
1842   SDValue NewLHS = N->getOperand(2), NewRHS = N->getOperand(3);
1843   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(1))->get();
1844   SDValue Chain;
1845   FloatExpandSetCCOperands(NewLHS, NewRHS, CCCode, SDLoc(N), Chain);
1846 
1847   // If ExpandSetCCOperands returned a scalar, we need to compare the result
1848   // against zero to select between true and false values.
1849   if (!NewRHS.getNode()) {
1850     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
1851     CCCode = ISD::SETNE;
1852   }
1853 
1854   // Update N to have the operands specified.
1855   return SDValue(DAG.UpdateNodeOperands(N, N->getOperand(0),
1856                                 DAG.getCondCode(CCCode), NewLHS, NewRHS,
1857                                 N->getOperand(4)), 0);
1858 }
1859 
1860 SDValue DAGTypeLegalizer::ExpandFloatOp_FCOPYSIGN(SDNode *N) {
1861   assert(N->getOperand(1).getValueType() == MVT::ppcf128 &&
1862          "Logic only correct for ppcf128!");
1863   SDValue Lo, Hi;
1864   GetExpandedFloat(N->getOperand(1), Lo, Hi);
1865   // The ppcf128 value is providing only the sign; take it from the
1866   // higher-order double (which must have the larger magnitude).
1867   return DAG.getNode(ISD::FCOPYSIGN, SDLoc(N),
1868                      N->getValueType(0), N->getOperand(0), Hi);
1869 }
1870 
1871 SDValue DAGTypeLegalizer::ExpandFloatOp_FP_ROUND(SDNode *N) {
1872   bool IsStrict = N->isStrictFPOpcode();
1873   assert(N->getOperand(IsStrict ? 1 : 0).getValueType() == MVT::ppcf128 &&
1874          "Logic only correct for ppcf128!");
1875   SDValue Lo, Hi;
1876   GetExpandedFloat(N->getOperand(IsStrict ? 1 : 0), Lo, Hi);
1877 
1878   if (!IsStrict)
1879     // Round it the rest of the way (e.g. to f32) if needed.
1880     return DAG.getNode(ISD::FP_ROUND, SDLoc(N),
1881                        N->getValueType(0), Hi, N->getOperand(1));
1882 
1883   // Eliminate the node if the input float type is the same as the output float
1884   // type.
1885   if (Hi.getValueType() == N->getValueType(0)) {
1886     // Connect the output chain to the input chain, unlinking the node.
1887     ReplaceValueWith(SDValue(N, 1), N->getOperand(0));
1888     ReplaceValueWith(SDValue(N, 0), Hi);
1889     return SDValue();
1890   }
1891 
1892   SDValue Expansion = DAG.getNode(ISD::STRICT_FP_ROUND, SDLoc(N),
1893                                   {N->getValueType(0), MVT::Other},
1894                                   {N->getOperand(0), Hi, N->getOperand(2)});
1895   ReplaceValueWith(SDValue(N, 1), Expansion.getValue(1));
1896   ReplaceValueWith(SDValue(N, 0), Expansion);
1897   return SDValue();
1898 }
1899 
1900 SDValue DAGTypeLegalizer::ExpandFloatOp_FP_TO_XINT(SDNode *N) {
1901   EVT RVT = N->getValueType(0);
1902   SDLoc dl(N);
1903 
1904   bool IsStrict = N->isStrictFPOpcode();
1905   bool Signed = N->getOpcode() == ISD::FP_TO_SINT ||
1906                 N->getOpcode() == ISD::STRICT_FP_TO_SINT;
1907   SDValue Op = N->getOperand(IsStrict ? 1 : 0);
1908   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1909 
1910   EVT NVT;
1911   RTLIB::Libcall LC = findFPToIntLibcall(Op.getValueType(), RVT, NVT, Signed);
1912   assert(LC != RTLIB::UNKNOWN_LIBCALL && NVT.isSimple() &&
1913          "Unsupported FP_TO_XINT!");
1914   TargetLowering::MakeLibCallOptions CallOptions;
1915   std::pair<SDValue, SDValue> Tmp =
1916       TLI.makeLibCall(DAG, LC, NVT, Op, CallOptions, dl, Chain);
1917   if (!IsStrict)
1918     return Tmp.first;
1919 
1920   ReplaceValueWith(SDValue(N, 1), Tmp.second);
1921   ReplaceValueWith(SDValue(N, 0), Tmp.first);
1922   return SDValue();
1923 }
1924 
1925 SDValue DAGTypeLegalizer::ExpandFloatOp_SELECT_CC(SDNode *N) {
1926   SDValue NewLHS = N->getOperand(0), NewRHS = N->getOperand(1);
1927   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(4))->get();
1928   SDValue Chain;
1929   FloatExpandSetCCOperands(NewLHS, NewRHS, CCCode, SDLoc(N), Chain);
1930 
1931   // If ExpandSetCCOperands returned a scalar, we need to compare the result
1932   // against zero to select between true and false values.
1933   if (!NewRHS.getNode()) {
1934     NewRHS = DAG.getConstant(0, SDLoc(N), NewLHS.getValueType());
1935     CCCode = ISD::SETNE;
1936   }
1937 
1938   // Update N to have the operands specified.
1939   return SDValue(DAG.UpdateNodeOperands(N, NewLHS, NewRHS,
1940                                 N->getOperand(2), N->getOperand(3),
1941                                 DAG.getCondCode(CCCode)), 0);
1942 }
1943 
1944 SDValue DAGTypeLegalizer::ExpandFloatOp_SETCC(SDNode *N) {
1945   bool IsStrict = N->isStrictFPOpcode();
1946   SDValue NewLHS = N->getOperand(IsStrict ? 1 : 0);
1947   SDValue NewRHS = N->getOperand(IsStrict ? 2 : 1);
1948   SDValue Chain = IsStrict ? N->getOperand(0) : SDValue();
1949   ISD::CondCode CCCode =
1950       cast<CondCodeSDNode>(N->getOperand(IsStrict ? 3 : 2))->get();
1951   FloatExpandSetCCOperands(NewLHS, NewRHS, CCCode, SDLoc(N), Chain,
1952                            N->getOpcode() == ISD::STRICT_FSETCCS);
1953 
1954   // FloatExpandSetCCOperands always returned a scalar.
1955   assert(!NewRHS.getNode() && "Expect to return scalar");
1956   assert(NewLHS.getValueType() == N->getValueType(0) &&
1957          "Unexpected setcc expansion!");
1958   if (Chain) {
1959     ReplaceValueWith(SDValue(N, 0), NewLHS);
1960     ReplaceValueWith(SDValue(N, 1), Chain);
1961     return SDValue();
1962   }
1963   return NewLHS;
1964 }
1965 
1966 SDValue DAGTypeLegalizer::ExpandFloatOp_STORE(SDNode *N, unsigned OpNo) {
1967   if (ISD::isNormalStore(N))
1968     return ExpandOp_NormalStore(N, OpNo);
1969 
1970   assert(ISD::isUNINDEXEDStore(N) && "Indexed store during type legalization!");
1971   assert(OpNo == 1 && "Can only expand the stored value so far");
1972   StoreSDNode *ST = cast<StoreSDNode>(N);
1973 
1974   SDValue Chain = ST->getChain();
1975   SDValue Ptr = ST->getBasePtr();
1976 
1977   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(),
1978                                      ST->getValue().getValueType());
1979   assert(NVT.isByteSized() && "Expanded type not byte sized!");
1980   assert(ST->getMemoryVT().bitsLE(NVT) && "Float type not round?");
1981   (void)NVT;
1982 
1983   SDValue Lo, Hi;
1984   GetExpandedOp(ST->getValue(), Lo, Hi);
1985 
1986   return DAG.getTruncStore(Chain, SDLoc(N), Hi, Ptr,
1987                            ST->getMemoryVT(), ST->getMemOperand());
1988 }
1989 
1990 SDValue DAGTypeLegalizer::ExpandFloatOp_LROUND(SDNode *N) {
1991   EVT RVT = N->getValueType(0);
1992   EVT RetVT = N->getOperand(0).getValueType();
1993   TargetLowering::MakeLibCallOptions CallOptions;
1994   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
1995                                            RTLIB::LROUND_F32,
1996                                            RTLIB::LROUND_F64,
1997                                            RTLIB::LROUND_F80,
1998                                            RTLIB::LROUND_F128,
1999                                            RTLIB::LROUND_PPCF128),
2000                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
2001 }
2002 
2003 SDValue DAGTypeLegalizer::ExpandFloatOp_LLROUND(SDNode *N) {
2004   EVT RVT = N->getValueType(0);
2005   EVT RetVT = N->getOperand(0).getValueType();
2006   TargetLowering::MakeLibCallOptions CallOptions;
2007   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
2008                                            RTLIB::LLROUND_F32,
2009                                            RTLIB::LLROUND_F64,
2010                                            RTLIB::LLROUND_F80,
2011                                            RTLIB::LLROUND_F128,
2012                                            RTLIB::LLROUND_PPCF128),
2013                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
2014 }
2015 
2016 SDValue DAGTypeLegalizer::ExpandFloatOp_LRINT(SDNode *N) {
2017   EVT RVT = N->getValueType(0);
2018   EVT RetVT = N->getOperand(0).getValueType();
2019   TargetLowering::MakeLibCallOptions CallOptions;
2020   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
2021                                            RTLIB::LRINT_F32,
2022                                            RTLIB::LRINT_F64,
2023                                            RTLIB::LRINT_F80,
2024                                            RTLIB::LRINT_F128,
2025                                            RTLIB::LRINT_PPCF128),
2026                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
2027 }
2028 
2029 SDValue DAGTypeLegalizer::ExpandFloatOp_LLRINT(SDNode *N) {
2030   EVT RVT = N->getValueType(0);
2031   EVT RetVT = N->getOperand(0).getValueType();
2032   TargetLowering::MakeLibCallOptions CallOptions;
2033   return TLI.makeLibCall(DAG, GetFPLibCall(RetVT,
2034                                            RTLIB::LLRINT_F32,
2035                                            RTLIB::LLRINT_F64,
2036                                            RTLIB::LLRINT_F80,
2037                                            RTLIB::LLRINT_F128,
2038                                            RTLIB::LLRINT_PPCF128),
2039                          RVT, N->getOperand(0), CallOptions, SDLoc(N)).first;
2040 }
2041 
2042 //===----------------------------------------------------------------------===//
2043 //  Float Operand Promotion
2044 //===----------------------------------------------------------------------===//
2045 //
2046 
2047 static ISD::NodeType GetPromotionOpcode(EVT OpVT, EVT RetVT) {
2048   if (OpVT == MVT::f16) {
2049       return ISD::FP16_TO_FP;
2050   } else if (RetVT == MVT::f16) {
2051       return ISD::FP_TO_FP16;
2052   }
2053 
2054   report_fatal_error("Attempt at an invalid promotion-related conversion");
2055 }
2056 
2057 bool DAGTypeLegalizer::PromoteFloatOperand(SDNode *N, unsigned OpNo) {
2058   LLVM_DEBUG(dbgs() << "Promote float operand " << OpNo << ": "; N->dump(&DAG);
2059              dbgs() << "\n");
2060   SDValue R = SDValue();
2061 
2062   if (CustomLowerNode(N, N->getOperand(OpNo).getValueType(), false)) {
2063     LLVM_DEBUG(dbgs() << "Node has been custom lowered, done\n");
2064     return false;
2065   }
2066 
2067   // Nodes that use a promotion-requiring floating point operand, but doesn't
2068   // produce a promotion-requiring floating point result, need to be legalized
2069   // to use the promoted float operand.  Nodes that produce at least one
2070   // promotion-requiring floating point result have their operands legalized as
2071   // a part of PromoteFloatResult.
2072   switch (N->getOpcode()) {
2073     default:
2074   #ifndef NDEBUG
2075       dbgs() << "PromoteFloatOperand Op #" << OpNo << ": ";
2076       N->dump(&DAG); dbgs() << "\n";
2077   #endif
2078       llvm_unreachable("Do not know how to promote this operator's operand!");
2079 
2080     case ISD::BITCAST:    R = PromoteFloatOp_BITCAST(N, OpNo); break;
2081     case ISD::FCOPYSIGN:  R = PromoteFloatOp_FCOPYSIGN(N, OpNo); break;
2082     case ISD::FP_TO_SINT:
2083     case ISD::FP_TO_UINT: R = PromoteFloatOp_FP_TO_XINT(N, OpNo); break;
2084     case ISD::FP_TO_SINT_SAT:
2085     case ISD::FP_TO_UINT_SAT:
2086                           R = PromoteFloatOp_FP_TO_XINT_SAT(N, OpNo); break;
2087     case ISD::FP_EXTEND:  R = PromoteFloatOp_FP_EXTEND(N, OpNo); break;
2088     case ISD::SELECT_CC:  R = PromoteFloatOp_SELECT_CC(N, OpNo); break;
2089     case ISD::SETCC:      R = PromoteFloatOp_SETCC(N, OpNo); break;
2090     case ISD::STORE:      R = PromoteFloatOp_STORE(N, OpNo); break;
2091   }
2092 
2093   if (R.getNode())
2094     ReplaceValueWith(SDValue(N, 0), R);
2095   return false;
2096 }
2097 
2098 SDValue DAGTypeLegalizer::PromoteFloatOp_BITCAST(SDNode *N, unsigned OpNo) {
2099   SDValue Op = N->getOperand(0);
2100   EVT OpVT = Op->getValueType(0);
2101 
2102   SDValue Promoted = GetPromotedFloat(N->getOperand(0));
2103   EVT PromotedVT = Promoted->getValueType(0);
2104 
2105   // Convert the promoted float value to the desired IVT.
2106   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), OpVT.getSizeInBits());
2107   SDValue Convert = DAG.getNode(GetPromotionOpcode(PromotedVT, OpVT), SDLoc(N),
2108                                 IVT, Promoted);
2109   // The final result type might not be an scalar so we need a bitcast. The
2110   // bitcast will be further legalized if needed.
2111   return DAG.getBitcast(N->getValueType(0), Convert);
2112 }
2113 
2114 // Promote Operand 1 of FCOPYSIGN.  Operand 0 ought to be handled by
2115 // PromoteFloatRes_FCOPYSIGN.
2116 SDValue DAGTypeLegalizer::PromoteFloatOp_FCOPYSIGN(SDNode *N, unsigned OpNo) {
2117   assert (OpNo == 1 && "Only Operand 1 must need promotion here");
2118   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2119 
2120   return DAG.getNode(N->getOpcode(), SDLoc(N), N->getValueType(0),
2121                      N->getOperand(0), Op1);
2122 }
2123 
2124 // Convert the promoted float value to the desired integer type
2125 SDValue DAGTypeLegalizer::PromoteFloatOp_FP_TO_XINT(SDNode *N, unsigned OpNo) {
2126   SDValue Op = GetPromotedFloat(N->getOperand(0));
2127   return DAG.getNode(N->getOpcode(), SDLoc(N), N->getValueType(0), Op);
2128 }
2129 
2130 SDValue DAGTypeLegalizer::PromoteFloatOp_FP_TO_XINT_SAT(SDNode *N,
2131                                                         unsigned OpNo) {
2132   SDValue Op = GetPromotedFloat(N->getOperand(0));
2133   return DAG.getNode(N->getOpcode(), SDLoc(N), N->getValueType(0), Op,
2134                      N->getOperand(1));
2135 }
2136 
2137 SDValue DAGTypeLegalizer::PromoteFloatOp_FP_EXTEND(SDNode *N, unsigned OpNo) {
2138   SDValue Op = GetPromotedFloat(N->getOperand(0));
2139   EVT VT = N->getValueType(0);
2140 
2141   // Desired VT is same as promoted type.  Use promoted float directly.
2142   if (VT == Op->getValueType(0))
2143     return Op;
2144 
2145   // Else, extend the promoted float value to the desired VT.
2146   return DAG.getNode(ISD::FP_EXTEND, SDLoc(N), VT, Op);
2147 }
2148 
2149 // Promote the float operands used for comparison.  The true- and false-
2150 // operands have the same type as the result and are promoted, if needed, by
2151 // PromoteFloatRes_SELECT_CC
2152 SDValue DAGTypeLegalizer::PromoteFloatOp_SELECT_CC(SDNode *N, unsigned OpNo) {
2153   SDValue LHS = GetPromotedFloat(N->getOperand(0));
2154   SDValue RHS = GetPromotedFloat(N->getOperand(1));
2155 
2156   return DAG.getNode(ISD::SELECT_CC, SDLoc(N), N->getValueType(0),
2157                      LHS, RHS, N->getOperand(2), N->getOperand(3),
2158                      N->getOperand(4));
2159 }
2160 
2161 // Construct a SETCC that compares the promoted values and sets the conditional
2162 // code.
2163 SDValue DAGTypeLegalizer::PromoteFloatOp_SETCC(SDNode *N, unsigned OpNo) {
2164   EVT VT = N->getValueType(0);
2165   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2166   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2167   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(2))->get();
2168 
2169   return DAG.getSetCC(SDLoc(N), VT, Op0, Op1, CCCode);
2170 
2171 }
2172 
2173 // Lower the promoted Float down to the integer value of same size and construct
2174 // a STORE of the integer value.
2175 SDValue DAGTypeLegalizer::PromoteFloatOp_STORE(SDNode *N, unsigned OpNo) {
2176   StoreSDNode *ST = cast<StoreSDNode>(N);
2177   SDValue Val = ST->getValue();
2178   SDLoc DL(N);
2179 
2180   SDValue Promoted = GetPromotedFloat(Val);
2181   EVT VT = ST->getOperand(1).getValueType();
2182   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2183 
2184   SDValue NewVal;
2185   NewVal = DAG.getNode(GetPromotionOpcode(Promoted.getValueType(), VT), DL,
2186                        IVT, Promoted);
2187 
2188   return DAG.getStore(ST->getChain(), DL, NewVal, ST->getBasePtr(),
2189                       ST->getMemOperand());
2190 }
2191 
2192 //===----------------------------------------------------------------------===//
2193 //  Float Result Promotion
2194 //===----------------------------------------------------------------------===//
2195 
2196 void DAGTypeLegalizer::PromoteFloatResult(SDNode *N, unsigned ResNo) {
2197   LLVM_DEBUG(dbgs() << "Promote float result " << ResNo << ": "; N->dump(&DAG);
2198              dbgs() << "\n");
2199   SDValue R = SDValue();
2200 
2201   // See if the target wants to custom expand this node.
2202   if (CustomLowerNode(N, N->getValueType(ResNo), true)) {
2203     LLVM_DEBUG(dbgs() << "Node has been custom expanded, done\n");
2204     return;
2205   }
2206 
2207   switch (N->getOpcode()) {
2208     // These opcodes cannot appear if promotion of FP16 is done in the backend
2209     // instead of Clang
2210     case ISD::FP16_TO_FP:
2211     case ISD::FP_TO_FP16:
2212     default:
2213 #ifndef NDEBUG
2214       dbgs() << "PromoteFloatResult #" << ResNo << ": ";
2215       N->dump(&DAG); dbgs() << "\n";
2216 #endif
2217       llvm_unreachable("Do not know how to promote this operator's result!");
2218 
2219     case ISD::BITCAST:    R = PromoteFloatRes_BITCAST(N); break;
2220     case ISD::ConstantFP: R = PromoteFloatRes_ConstantFP(N); break;
2221     case ISD::EXTRACT_VECTOR_ELT:
2222                           R = PromoteFloatRes_EXTRACT_VECTOR_ELT(N); break;
2223     case ISD::FCOPYSIGN:  R = PromoteFloatRes_FCOPYSIGN(N); break;
2224 
2225     // Unary FP Operations
2226     case ISD::FABS:
2227     case ISD::FCBRT:
2228     case ISD::FCEIL:
2229     case ISD::FCOS:
2230     case ISD::FEXP:
2231     case ISD::FEXP2:
2232     case ISD::FFLOOR:
2233     case ISD::FLOG:
2234     case ISD::FLOG2:
2235     case ISD::FLOG10:
2236     case ISD::FNEARBYINT:
2237     case ISD::FNEG:
2238     case ISD::FRINT:
2239     case ISD::FROUND:
2240     case ISD::FROUNDEVEN:
2241     case ISD::FSIN:
2242     case ISD::FSQRT:
2243     case ISD::FTRUNC:
2244     case ISD::FCANONICALIZE: R = PromoteFloatRes_UnaryOp(N); break;
2245 
2246     // Binary FP Operations
2247     case ISD::FADD:
2248     case ISD::FDIV:
2249     case ISD::FMAXIMUM:
2250     case ISD::FMINIMUM:
2251     case ISD::FMAXNUM:
2252     case ISD::FMINNUM:
2253     case ISD::FMUL:
2254     case ISD::FPOW:
2255     case ISD::FREM:
2256     case ISD::FSUB:       R = PromoteFloatRes_BinOp(N); break;
2257 
2258     case ISD::FMA:        // FMA is same as FMAD
2259     case ISD::FMAD:       R = PromoteFloatRes_FMAD(N); break;
2260 
2261     case ISD::FPOWI:      R = PromoteFloatRes_FPOWI(N); break;
2262 
2263     case ISD::FP_ROUND:   R = PromoteFloatRes_FP_ROUND(N); break;
2264     case ISD::LOAD:       R = PromoteFloatRes_LOAD(N); break;
2265     case ISD::SELECT:     R = PromoteFloatRes_SELECT(N); break;
2266     case ISD::SELECT_CC:  R = PromoteFloatRes_SELECT_CC(N); break;
2267 
2268     case ISD::SINT_TO_FP:
2269     case ISD::UINT_TO_FP: R = PromoteFloatRes_XINT_TO_FP(N); break;
2270     case ISD::UNDEF:      R = PromoteFloatRes_UNDEF(N); break;
2271     case ISD::ATOMIC_SWAP: R = BitcastToInt_ATOMIC_SWAP(N); break;
2272     case ISD::VECREDUCE_FADD:
2273     case ISD::VECREDUCE_FMUL:
2274     case ISD::VECREDUCE_FMIN:
2275     case ISD::VECREDUCE_FMAX:
2276       R = PromoteFloatRes_VECREDUCE(N);
2277       break;
2278     case ISD::VECREDUCE_SEQ_FADD:
2279     case ISD::VECREDUCE_SEQ_FMUL:
2280       R = PromoteFloatRes_VECREDUCE_SEQ(N);
2281       break;
2282   }
2283 
2284   if (R.getNode())
2285     SetPromotedFloat(SDValue(N, ResNo), R);
2286 }
2287 
2288 // Bitcast from i16 to f16:  convert the i16 to a f32 value instead.
2289 // At this point, it is not possible to determine if the bitcast value is
2290 // eventually stored to memory or promoted to f32 or promoted to a floating
2291 // point at a higher precision.  Some of these cases are handled by FP_EXTEND,
2292 // STORE promotion handlers.
2293 SDValue DAGTypeLegalizer::PromoteFloatRes_BITCAST(SDNode *N) {
2294   EVT VT = N->getValueType(0);
2295   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2296   // Input type isn't guaranteed to be a scalar int so bitcast if not. The
2297   // bitcast will be legalized further if necessary.
2298   EVT IVT = EVT::getIntegerVT(*DAG.getContext(),
2299                               N->getOperand(0).getValueType().getSizeInBits());
2300   SDValue Cast = DAG.getBitcast(IVT, N->getOperand(0));
2301   return DAG.getNode(GetPromotionOpcode(VT, NVT), SDLoc(N), NVT, Cast);
2302 }
2303 
2304 SDValue DAGTypeLegalizer::PromoteFloatRes_ConstantFP(SDNode *N) {
2305   ConstantFPSDNode *CFPNode = cast<ConstantFPSDNode>(N);
2306   EVT VT = N->getValueType(0);
2307   SDLoc DL(N);
2308 
2309   // Get the (bit-cast) APInt of the APFloat and build an integer constant
2310   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2311   SDValue C = DAG.getConstant(CFPNode->getValueAPF().bitcastToAPInt(), DL,
2312                               IVT);
2313 
2314   // Convert the Constant to the desired FP type
2315   // FIXME We might be able to do the conversion during compilation and get rid
2316   // of it from the object code
2317   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2318   return DAG.getNode(GetPromotionOpcode(VT, NVT), DL, NVT, C);
2319 }
2320 
2321 // If the Index operand is a constant, try to redirect the extract operation to
2322 // the correct legalized vector.  If not, bit-convert the input vector to
2323 // equivalent integer vector.  Extract the element as an (bit-cast) integer
2324 // value and convert it to the promoted type.
2325 SDValue DAGTypeLegalizer::PromoteFloatRes_EXTRACT_VECTOR_ELT(SDNode *N) {
2326   SDLoc DL(N);
2327 
2328   // If the index is constant, try to extract the value from the legalized
2329   // vector type.
2330   if (isa<ConstantSDNode>(N->getOperand(1))) {
2331     SDValue Vec = N->getOperand(0);
2332     SDValue Idx = N->getOperand(1);
2333     EVT VecVT = Vec->getValueType(0);
2334     EVT EltVT = VecVT.getVectorElementType();
2335 
2336     uint64_t IdxVal = cast<ConstantSDNode>(Idx)->getZExtValue();
2337 
2338     switch (getTypeAction(VecVT)) {
2339     default: break;
2340     case TargetLowering::TypeScalarizeVector: {
2341       SDValue Res = GetScalarizedVector(N->getOperand(0));
2342       ReplaceValueWith(SDValue(N, 0), Res);
2343       return SDValue();
2344     }
2345     case TargetLowering::TypeWidenVector: {
2346       Vec = GetWidenedVector(Vec);
2347       SDValue Res = DAG.getNode(N->getOpcode(), DL, EltVT, Vec, Idx);
2348       ReplaceValueWith(SDValue(N, 0), Res);
2349       return SDValue();
2350     }
2351     case TargetLowering::TypeSplitVector: {
2352       SDValue Lo, Hi;
2353       GetSplitVector(Vec, Lo, Hi);
2354 
2355       uint64_t LoElts = Lo.getValueType().getVectorNumElements();
2356       SDValue Res;
2357       if (IdxVal < LoElts)
2358         Res = DAG.getNode(N->getOpcode(), DL, EltVT, Lo, Idx);
2359       else
2360         Res = DAG.getNode(N->getOpcode(), DL, EltVT, Hi,
2361                           DAG.getConstant(IdxVal - LoElts, DL,
2362                                           Idx.getValueType()));
2363       ReplaceValueWith(SDValue(N, 0), Res);
2364       return SDValue();
2365     }
2366 
2367     }
2368   }
2369 
2370   // Bit-convert the input vector to the equivalent integer vector
2371   SDValue NewOp = BitConvertVectorToIntegerVector(N->getOperand(0));
2372   EVT IVT = NewOp.getValueType().getVectorElementType();
2373 
2374   // Extract the element as an (bit-cast) integer value
2375   SDValue NewVal = DAG.getNode(ISD::EXTRACT_VECTOR_ELT, DL, IVT,
2376                                NewOp, N->getOperand(1));
2377 
2378   // Convert the element to the desired FP type
2379   EVT VT = N->getValueType(0);
2380   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2381   return DAG.getNode(GetPromotionOpcode(VT, NVT), SDLoc(N), NVT, NewVal);
2382 }
2383 
2384 // FCOPYSIGN(X, Y) returns the value of X with the sign of Y.  If the result
2385 // needs promotion, so does the argument X.  Note that Y, if needed, will be
2386 // handled during operand promotion.
2387 SDValue DAGTypeLegalizer::PromoteFloatRes_FCOPYSIGN(SDNode *N) {
2388   EVT VT = N->getValueType(0);
2389   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2390   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2391 
2392   SDValue Op1 = N->getOperand(1);
2393 
2394   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1);
2395 }
2396 
2397 // Unary operation where the result and the operand have PromoteFloat type
2398 // action.  Construct a new SDNode with the promoted float value of the old
2399 // operand.
2400 SDValue DAGTypeLegalizer::PromoteFloatRes_UnaryOp(SDNode *N) {
2401   EVT VT = N->getValueType(0);
2402   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2403   SDValue Op = GetPromotedFloat(N->getOperand(0));
2404 
2405   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op);
2406 }
2407 
2408 // Binary operations where the result and both operands have PromoteFloat type
2409 // action.  Construct a new SDNode with the promoted float values of the old
2410 // operands.
2411 SDValue DAGTypeLegalizer::PromoteFloatRes_BinOp(SDNode *N) {
2412   EVT VT = N->getValueType(0);
2413   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2414   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2415   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2416   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1, N->getFlags());
2417 }
2418 
2419 SDValue DAGTypeLegalizer::PromoteFloatRes_FMAD(SDNode *N) {
2420   EVT VT = N->getValueType(0);
2421   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2422   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2423   SDValue Op1 = GetPromotedFloat(N->getOperand(1));
2424   SDValue Op2 = GetPromotedFloat(N->getOperand(2));
2425 
2426   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1, Op2);
2427 }
2428 
2429 // Promote the Float (first) operand and retain the Integer (second) operand
2430 SDValue DAGTypeLegalizer::PromoteFloatRes_FPOWI(SDNode *N) {
2431   EVT VT = N->getValueType(0);
2432   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2433   SDValue Op0 = GetPromotedFloat(N->getOperand(0));
2434   SDValue Op1 = N->getOperand(1);
2435 
2436   return DAG.getNode(N->getOpcode(), SDLoc(N), NVT, Op0, Op1);
2437 }
2438 
2439 // Explicit operation to reduce precision.  Reduce the value to half precision
2440 // and promote it back to the legal type.
2441 SDValue DAGTypeLegalizer::PromoteFloatRes_FP_ROUND(SDNode *N) {
2442   SDLoc DL(N);
2443 
2444   SDValue Op = N->getOperand(0);
2445   EVT VT = N->getValueType(0);
2446   EVT OpVT = Op->getValueType(0);
2447   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
2448   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2449 
2450   // Round promoted float to desired precision
2451   SDValue Round = DAG.getNode(GetPromotionOpcode(OpVT, VT), DL, IVT, Op);
2452   // Promote it back to the legal output type
2453   return DAG.getNode(GetPromotionOpcode(VT, NVT), DL, NVT, Round);
2454 }
2455 
2456 SDValue DAGTypeLegalizer::PromoteFloatRes_LOAD(SDNode *N) {
2457   LoadSDNode *L = cast<LoadSDNode>(N);
2458   EVT VT = N->getValueType(0);
2459 
2460   // Load the value as an integer value with the same number of bits.
2461   EVT IVT = EVT::getIntegerVT(*DAG.getContext(), VT.getSizeInBits());
2462   SDValue newL = DAG.getLoad(
2463       L->getAddressingMode(), L->getExtensionType(), IVT, SDLoc(N),
2464       L->getChain(), L->getBasePtr(), L->getOffset(), L->getPointerInfo(), IVT,
2465       L->getOriginalAlign(), L->getMemOperand()->getFlags(), L->getAAInfo());
2466   // Legalize the chain result by replacing uses of the old value chain with the
2467   // new one
2468   ReplaceValueWith(SDValue(N, 1), newL.getValue(1));
2469 
2470   // Convert the integer value to the desired FP type
2471   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2472   return DAG.getNode(GetPromotionOpcode(VT, NVT), SDLoc(N), NVT, newL);
2473 }
2474 
2475 // Construct a new SELECT node with the promoted true- and false- values.
2476 SDValue DAGTypeLegalizer::PromoteFloatRes_SELECT(SDNode *N) {
2477   SDValue TrueVal = GetPromotedFloat(N->getOperand(1));
2478   SDValue FalseVal = GetPromotedFloat(N->getOperand(2));
2479 
2480   return DAG.getNode(ISD::SELECT, SDLoc(N), TrueVal->getValueType(0),
2481                      N->getOperand(0), TrueVal, FalseVal);
2482 }
2483 
2484 // Construct a new SELECT_CC node with the promoted true- and false- values.
2485 // The operands used for comparison are promoted by PromoteFloatOp_SELECT_CC.
2486 SDValue DAGTypeLegalizer::PromoteFloatRes_SELECT_CC(SDNode *N) {
2487   SDValue TrueVal = GetPromotedFloat(N->getOperand(2));
2488   SDValue FalseVal = GetPromotedFloat(N->getOperand(3));
2489 
2490   return DAG.getNode(ISD::SELECT_CC, SDLoc(N),
2491                      TrueVal.getNode()->getValueType(0), N->getOperand(0),
2492                      N->getOperand(1), TrueVal, FalseVal, N->getOperand(4));
2493 }
2494 
2495 // Construct a SDNode that transforms the SINT or UINT operand to the promoted
2496 // float type.
2497 SDValue DAGTypeLegalizer::PromoteFloatRes_XINT_TO_FP(SDNode *N) {
2498   SDLoc DL(N);
2499   EVT VT = N->getValueType(0);
2500   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2501   SDValue NV = DAG.getNode(N->getOpcode(), DL, NVT, N->getOperand(0));
2502   // Round the value to the desired precision (that of the source type).
2503   return DAG.getNode(
2504       ISD::FP_EXTEND, DL, NVT,
2505       DAG.getNode(ISD::FP_ROUND, DL, VT, NV, DAG.getIntPtrConstant(0, DL)));
2506 }
2507 
2508 SDValue DAGTypeLegalizer::PromoteFloatRes_UNDEF(SDNode *N) {
2509   return DAG.getUNDEF(TLI.getTypeToTransformTo(*DAG.getContext(),
2510                                                N->getValueType(0)));
2511 }
2512 
2513 SDValue DAGTypeLegalizer::PromoteFloatRes_VECREDUCE(SDNode *N) {
2514   // Expand and promote recursively.
2515   // TODO: This is non-optimal, but dealing with the concurrently happening
2516   // vector-legalization is non-trivial. We could do something similar to
2517   // PromoteFloatRes_EXTRACT_VECTOR_ELT here.
2518   ReplaceValueWith(SDValue(N, 0), TLI.expandVecReduce(N, DAG));
2519   return SDValue();
2520 }
2521 
2522 SDValue DAGTypeLegalizer::PromoteFloatRes_VECREDUCE_SEQ(SDNode *N) {
2523   ReplaceValueWith(SDValue(N, 0), TLI.expandVecReduceSeq(N, DAG));
2524   return SDValue();
2525 }
2526 
2527 SDValue DAGTypeLegalizer::BitcastToInt_ATOMIC_SWAP(SDNode *N) {
2528   EVT VT = N->getValueType(0);
2529 
2530   AtomicSDNode *AM = cast<AtomicSDNode>(N);
2531   SDLoc SL(N);
2532 
2533   SDValue CastVal = BitConvertToInteger(AM->getVal());
2534   EVT CastVT = CastVal.getValueType();
2535 
2536   SDValue NewAtomic
2537     = DAG.getAtomic(ISD::ATOMIC_SWAP, SL, CastVT,
2538                     DAG.getVTList(CastVT, MVT::Other),
2539                     { AM->getChain(), AM->getBasePtr(), CastVal },
2540                     AM->getMemOperand());
2541 
2542   SDValue Result = NewAtomic;
2543 
2544   if (getTypeAction(VT) == TargetLowering::TypePromoteFloat) {
2545     EVT NFPVT = TLI.getTypeToTransformTo(*DAG.getContext(), VT);
2546     Result = DAG.getNode(GetPromotionOpcode(VT, NFPVT), SL, NFPVT,
2547                                      NewAtomic);
2548   }
2549 
2550   // Legalize the chain result by replacing uses of the old value chain with the
2551   // new one
2552   ReplaceValueWith(SDValue(N, 1), NewAtomic.getValue(1));
2553 
2554   return Result;
2555 
2556 }
2557 
2558 //===----------------------------------------------------------------------===//
2559 //  Half Result Soft Promotion
2560 //===----------------------------------------------------------------------===//
2561 
2562 void DAGTypeLegalizer::SoftPromoteHalfResult(SDNode *N, unsigned ResNo) {
2563   LLVM_DEBUG(dbgs() << "Soft promote half result " << ResNo << ": ";
2564              N->dump(&DAG); dbgs() << "\n");
2565   SDValue R = SDValue();
2566 
2567   // See if the target wants to custom expand this node.
2568   if (CustomLowerNode(N, N->getValueType(ResNo), true)) {
2569     LLVM_DEBUG(dbgs() << "Node has been custom expanded, done\n");
2570     return;
2571   }
2572 
2573   switch (N->getOpcode()) {
2574   default:
2575 #ifndef NDEBUG
2576     dbgs() << "SoftPromoteHalfResult #" << ResNo << ": ";
2577     N->dump(&DAG); dbgs() << "\n";
2578 #endif
2579     llvm_unreachable("Do not know how to soft promote this operator's result!");
2580 
2581   case ISD::BITCAST:    R = SoftPromoteHalfRes_BITCAST(N); break;
2582   case ISD::ConstantFP: R = SoftPromoteHalfRes_ConstantFP(N); break;
2583   case ISD::EXTRACT_VECTOR_ELT:
2584     R = SoftPromoteHalfRes_EXTRACT_VECTOR_ELT(N); break;
2585   case ISD::FCOPYSIGN:  R = SoftPromoteHalfRes_FCOPYSIGN(N); break;
2586   case ISD::STRICT_FP_ROUND:
2587   case ISD::FP_ROUND:   R = SoftPromoteHalfRes_FP_ROUND(N); break;
2588 
2589   // Unary FP Operations
2590   case ISD::FABS:
2591   case ISD::FCBRT:
2592   case ISD::FCEIL:
2593   case ISD::FCOS:
2594   case ISD::FEXP:
2595   case ISD::FEXP2:
2596   case ISD::FFLOOR:
2597   case ISD::FLOG:
2598   case ISD::FLOG2:
2599   case ISD::FLOG10:
2600   case ISD::FNEARBYINT:
2601   case ISD::FNEG:
2602   case ISD::FREEZE:
2603   case ISD::FRINT:
2604   case ISD::FROUND:
2605   case ISD::FROUNDEVEN:
2606   case ISD::FSIN:
2607   case ISD::FSQRT:
2608   case ISD::FTRUNC:
2609   case ISD::FCANONICALIZE: R = SoftPromoteHalfRes_UnaryOp(N); break;
2610 
2611   // Binary FP Operations
2612   case ISD::FADD:
2613   case ISD::FDIV:
2614   case ISD::FMAXIMUM:
2615   case ISD::FMINIMUM:
2616   case ISD::FMAXNUM:
2617   case ISD::FMINNUM:
2618   case ISD::FMUL:
2619   case ISD::FPOW:
2620   case ISD::FREM:
2621   case ISD::FSUB:        R = SoftPromoteHalfRes_BinOp(N); break;
2622 
2623   case ISD::FMA:         // FMA is same as FMAD
2624   case ISD::FMAD:        R = SoftPromoteHalfRes_FMAD(N); break;
2625 
2626   case ISD::FPOWI:       R = SoftPromoteHalfRes_FPOWI(N); break;
2627 
2628   case ISD::LOAD:        R = SoftPromoteHalfRes_LOAD(N); break;
2629   case ISD::SELECT:      R = SoftPromoteHalfRes_SELECT(N); break;
2630   case ISD::SELECT_CC:   R = SoftPromoteHalfRes_SELECT_CC(N); break;
2631   case ISD::SINT_TO_FP:
2632   case ISD::UINT_TO_FP:  R = SoftPromoteHalfRes_XINT_TO_FP(N); break;
2633   case ISD::UNDEF:       R = SoftPromoteHalfRes_UNDEF(N); break;
2634   case ISD::ATOMIC_SWAP: R = BitcastToInt_ATOMIC_SWAP(N); break;
2635   case ISD::VECREDUCE_FADD:
2636   case ISD::VECREDUCE_FMUL:
2637   case ISD::VECREDUCE_FMIN:
2638   case ISD::VECREDUCE_FMAX:
2639     R = SoftPromoteHalfRes_VECREDUCE(N);
2640     break;
2641   case ISD::VECREDUCE_SEQ_FADD:
2642   case ISD::VECREDUCE_SEQ_FMUL:
2643     R = SoftPromoteHalfRes_VECREDUCE_SEQ(N);
2644     break;
2645   }
2646 
2647   if (R.getNode())
2648     SetSoftPromotedHalf(SDValue(N, ResNo), R);
2649 }
2650 
2651 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_BITCAST(SDNode *N) {
2652   return BitConvertToInteger(N->getOperand(0));
2653 }
2654 
2655 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_ConstantFP(SDNode *N) {
2656   ConstantFPSDNode *CN = cast<ConstantFPSDNode>(N);
2657 
2658   // Get the (bit-cast) APInt of the APFloat and build an integer constant
2659   return DAG.getConstant(CN->getValueAPF().bitcastToAPInt(), SDLoc(CN),
2660                          MVT::i16);
2661 }
2662 
2663 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_EXTRACT_VECTOR_ELT(SDNode *N) {
2664   SDValue NewOp = BitConvertVectorToIntegerVector(N->getOperand(0));
2665   return DAG.getNode(ISD::EXTRACT_VECTOR_ELT, SDLoc(N),
2666                      NewOp.getValueType().getVectorElementType(), NewOp,
2667                      N->getOperand(1));
2668 }
2669 
2670 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_FCOPYSIGN(SDNode *N) {
2671   SDValue LHS = GetSoftPromotedHalf(N->getOperand(0));
2672   SDValue RHS = BitConvertToInteger(N->getOperand(1));
2673   SDLoc dl(N);
2674 
2675   EVT LVT = LHS.getValueType();
2676   EVT RVT = RHS.getValueType();
2677 
2678   unsigned LSize = LVT.getSizeInBits();
2679   unsigned RSize = RVT.getSizeInBits();
2680 
2681   // First get the sign bit of second operand.
2682   SDValue SignBit = DAG.getNode(
2683       ISD::SHL, dl, RVT, DAG.getConstant(1, dl, RVT),
2684       DAG.getConstant(RSize - 1, dl,
2685                       TLI.getShiftAmountTy(RVT, DAG.getDataLayout())));
2686   SignBit = DAG.getNode(ISD::AND, dl, RVT, RHS, SignBit);
2687 
2688   // Shift right or sign-extend it if the two operands have different types.
2689   int SizeDiff = RVT.getSizeInBits() - LVT.getSizeInBits();
2690   if (SizeDiff > 0) {
2691     SignBit =
2692         DAG.getNode(ISD::SRL, dl, RVT, SignBit,
2693                     DAG.getConstant(SizeDiff, dl,
2694                                     TLI.getShiftAmountTy(SignBit.getValueType(),
2695                                                          DAG.getDataLayout())));
2696     SignBit = DAG.getNode(ISD::TRUNCATE, dl, LVT, SignBit);
2697   } else if (SizeDiff < 0) {
2698     SignBit = DAG.getNode(ISD::ANY_EXTEND, dl, LVT, SignBit);
2699     SignBit =
2700         DAG.getNode(ISD::SHL, dl, LVT, SignBit,
2701                     DAG.getConstant(-SizeDiff, dl,
2702                                     TLI.getShiftAmountTy(SignBit.getValueType(),
2703                                                          DAG.getDataLayout())));
2704   }
2705 
2706   // Clear the sign bit of the first operand.
2707   SDValue Mask = DAG.getNode(
2708       ISD::SHL, dl, LVT, DAG.getConstant(1, dl, LVT),
2709       DAG.getConstant(LSize - 1, dl,
2710                       TLI.getShiftAmountTy(LVT, DAG.getDataLayout())));
2711   Mask = DAG.getNode(ISD::SUB, dl, LVT, Mask, DAG.getConstant(1, dl, LVT));
2712   LHS = DAG.getNode(ISD::AND, dl, LVT, LHS, Mask);
2713 
2714   // Or the value with the sign bit.
2715   return DAG.getNode(ISD::OR, dl, LVT, LHS, SignBit);
2716 }
2717 
2718 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_FMAD(SDNode *N) {
2719   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
2720   SDValue Op0 = GetSoftPromotedHalf(N->getOperand(0));
2721   SDValue Op1 = GetSoftPromotedHalf(N->getOperand(1));
2722   SDValue Op2 = GetSoftPromotedHalf(N->getOperand(2));
2723   SDLoc dl(N);
2724 
2725   // Promote to the larger FP type.
2726   Op0 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op0);
2727   Op1 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op1);
2728   Op2 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op2);
2729 
2730   SDValue Res = DAG.getNode(N->getOpcode(), dl, NVT, Op0, Op1, Op2);
2731 
2732   // Convert back to FP16 as an integer.
2733   return DAG.getNode(ISD::FP_TO_FP16, dl, MVT::i16, Res);
2734 }
2735 
2736 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_FPOWI(SDNode *N) {
2737   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
2738   SDValue Op0 = GetSoftPromotedHalf(N->getOperand(0));
2739   SDValue Op1 = N->getOperand(1);
2740   SDLoc dl(N);
2741 
2742   Op0 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op0);
2743 
2744   SDValue Res = DAG.getNode(N->getOpcode(), dl, NVT, Op0, Op1);
2745 
2746   // Convert back to FP16 as an integer.
2747   return DAG.getNode(ISD::FP_TO_FP16, dl, MVT::i16, Res);
2748 }
2749 
2750 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_FP_ROUND(SDNode *N) {
2751   if (N->isStrictFPOpcode()) {
2752     SDValue Res =
2753         DAG.getNode(ISD::STRICT_FP_TO_FP16, SDLoc(N), {MVT::i16, MVT::Other},
2754                     {N->getOperand(0), N->getOperand(1)});
2755     ReplaceValueWith(SDValue(N, 1), Res.getValue(1));
2756     return Res;
2757   }
2758 
2759   return DAG.getNode(ISD::FP_TO_FP16, SDLoc(N), MVT::i16, N->getOperand(0));
2760 }
2761 
2762 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_LOAD(SDNode *N) {
2763   LoadSDNode *L = cast<LoadSDNode>(N);
2764 
2765   // Load the value as an integer value with the same number of bits.
2766   assert(L->getExtensionType() == ISD::NON_EXTLOAD && "Unexpected extension!");
2767   SDValue NewL =
2768       DAG.getLoad(L->getAddressingMode(), L->getExtensionType(), MVT::i16,
2769                   SDLoc(N), L->getChain(), L->getBasePtr(), L->getOffset(),
2770                   L->getPointerInfo(), MVT::i16, L->getOriginalAlign(),
2771                   L->getMemOperand()->getFlags(), L->getAAInfo());
2772   // Legalize the chain result by replacing uses of the old value chain with the
2773   // new one
2774   ReplaceValueWith(SDValue(N, 1), NewL.getValue(1));
2775   return NewL;
2776 }
2777 
2778 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_SELECT(SDNode *N) {
2779   SDValue Op1 = GetSoftPromotedHalf(N->getOperand(1));
2780   SDValue Op2 = GetSoftPromotedHalf(N->getOperand(2));
2781   return DAG.getSelect(SDLoc(N), Op1.getValueType(), N->getOperand(0), Op1,
2782                        Op2);
2783 }
2784 
2785 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_SELECT_CC(SDNode *N) {
2786   SDValue Op2 = GetSoftPromotedHalf(N->getOperand(2));
2787   SDValue Op3 = GetSoftPromotedHalf(N->getOperand(3));
2788   return DAG.getNode(ISD::SELECT_CC, SDLoc(N), Op2.getValueType(),
2789                      N->getOperand(0), N->getOperand(1), Op2, Op3,
2790                      N->getOperand(4));
2791 }
2792 
2793 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_XINT_TO_FP(SDNode *N) {
2794   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
2795   SDLoc dl(N);
2796 
2797   SDValue Res = DAG.getNode(N->getOpcode(), dl, NVT, N->getOperand(0));
2798 
2799   // Round the value to the softened type.
2800   return DAG.getNode(ISD::FP_TO_FP16, dl, MVT::i16, Res);
2801 }
2802 
2803 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_UNDEF(SDNode *N) {
2804   return DAG.getUNDEF(MVT::i16);
2805 }
2806 
2807 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_UnaryOp(SDNode *N) {
2808   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
2809   SDValue Op = GetSoftPromotedHalf(N->getOperand(0));
2810   SDLoc dl(N);
2811 
2812   // Promote to the larger FP type.
2813   Op = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op);
2814 
2815   SDValue Res = DAG.getNode(N->getOpcode(), dl, NVT, Op);
2816 
2817   // Convert back to FP16 as an integer.
2818   return DAG.getNode(ISD::FP_TO_FP16, dl, MVT::i16, Res);
2819 }
2820 
2821 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_BinOp(SDNode *N) {
2822   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), N->getValueType(0));
2823   SDValue Op0 = GetSoftPromotedHalf(N->getOperand(0));
2824   SDValue Op1 = GetSoftPromotedHalf(N->getOperand(1));
2825   SDLoc dl(N);
2826 
2827   // Promote to the larger FP type.
2828   Op0 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op0);
2829   Op1 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op1);
2830 
2831   SDValue Res = DAG.getNode(N->getOpcode(), dl, NVT, Op0, Op1);
2832 
2833   // Convert back to FP16 as an integer.
2834   return DAG.getNode(ISD::FP_TO_FP16, dl, MVT::i16, Res);
2835 }
2836 
2837 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_VECREDUCE(SDNode *N) {
2838   // Expand and soften recursively.
2839   ReplaceValueWith(SDValue(N, 0), TLI.expandVecReduce(N, DAG));
2840   return SDValue();
2841 }
2842 
2843 SDValue DAGTypeLegalizer::SoftPromoteHalfRes_VECREDUCE_SEQ(SDNode *N) {
2844   // Expand and soften.
2845   ReplaceValueWith(SDValue(N, 0), TLI.expandVecReduceSeq(N, DAG));
2846   return SDValue();
2847 }
2848 
2849 //===----------------------------------------------------------------------===//
2850 //  Half Operand Soft Promotion
2851 //===----------------------------------------------------------------------===//
2852 
2853 bool DAGTypeLegalizer::SoftPromoteHalfOperand(SDNode *N, unsigned OpNo) {
2854   LLVM_DEBUG(dbgs() << "Soft promote half operand " << OpNo << ": ";
2855              N->dump(&DAG); dbgs() << "\n");
2856   SDValue Res = SDValue();
2857 
2858   if (CustomLowerNode(N, N->getOperand(OpNo).getValueType(), false)) {
2859     LLVM_DEBUG(dbgs() << "Node has been custom lowered, done\n");
2860     return false;
2861   }
2862 
2863   // Nodes that use a promotion-requiring floating point operand, but doesn't
2864   // produce a soft promotion-requiring floating point result, need to be
2865   // legalized to use the soft promoted float operand.  Nodes that produce at
2866   // least one soft promotion-requiring floating point result have their
2867   // operands legalized as a part of PromoteFloatResult.
2868   switch (N->getOpcode()) {
2869   default:
2870   #ifndef NDEBUG
2871     dbgs() << "SoftPromoteHalfOperand Op #" << OpNo << ": ";
2872     N->dump(&DAG); dbgs() << "\n";
2873   #endif
2874     llvm_unreachable("Do not know how to soft promote this operator's operand!");
2875 
2876   case ISD::BITCAST:    Res = SoftPromoteHalfOp_BITCAST(N); break;
2877   case ISD::FCOPYSIGN:  Res = SoftPromoteHalfOp_FCOPYSIGN(N, OpNo); break;
2878   case ISD::FP_TO_SINT:
2879   case ISD::FP_TO_UINT: Res = SoftPromoteHalfOp_FP_TO_XINT(N); break;
2880   case ISD::FP_TO_SINT_SAT:
2881   case ISD::FP_TO_UINT_SAT:
2882                         Res = SoftPromoteHalfOp_FP_TO_XINT_SAT(N); break;
2883   case ISD::STRICT_FP_EXTEND:
2884   case ISD::FP_EXTEND:  Res = SoftPromoteHalfOp_FP_EXTEND(N); break;
2885   case ISD::SELECT_CC:  Res = SoftPromoteHalfOp_SELECT_CC(N, OpNo); break;
2886   case ISD::SETCC:      Res = SoftPromoteHalfOp_SETCC(N); break;
2887   case ISD::STORE:      Res = SoftPromoteHalfOp_STORE(N, OpNo); break;
2888   }
2889 
2890   if (!Res.getNode())
2891     return false;
2892 
2893   assert(Res.getNode() != N && "Expected a new node!");
2894 
2895   assert(Res.getValueType() == N->getValueType(0) && N->getNumValues() == 1 &&
2896          "Invalid operand expansion");
2897 
2898   ReplaceValueWith(SDValue(N, 0), Res);
2899   return false;
2900 }
2901 
2902 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_BITCAST(SDNode *N) {
2903   SDValue Op0 = GetSoftPromotedHalf(N->getOperand(0));
2904 
2905   return DAG.getNode(ISD::BITCAST, SDLoc(N), N->getValueType(0), Op0);
2906 }
2907 
2908 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_FCOPYSIGN(SDNode *N,
2909                                                       unsigned OpNo) {
2910   assert(OpNo == 1 && "Only Operand 1 must need promotion here");
2911   SDValue Op1 = N->getOperand(1);
2912   SDLoc dl(N);
2913 
2914   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), Op1.getValueType());
2915 
2916   Op1 = GetSoftPromotedHalf(Op1);
2917   Op1 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op1);
2918 
2919   return DAG.getNode(N->getOpcode(), dl, N->getValueType(0), N->getOperand(0),
2920                      Op1);
2921 }
2922 
2923 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_FP_EXTEND(SDNode *N) {
2924   bool IsStrict = N->isStrictFPOpcode();
2925   SDValue Op = GetSoftPromotedHalf(N->getOperand(IsStrict ? 1 : 0));
2926 
2927   if (IsStrict) {
2928     SDValue Res =
2929         DAG.getNode(ISD::STRICT_FP16_TO_FP, SDLoc(N),
2930                     {N->getValueType(0), MVT::Other}, {N->getOperand(0), Op});
2931     ReplaceValueWith(SDValue(N, 1), Res.getValue(1));
2932     ReplaceValueWith(SDValue(N, 0), Res);
2933     return SDValue();
2934   }
2935 
2936   return DAG.getNode(ISD::FP16_TO_FP, SDLoc(N), N->getValueType(0), Op);
2937 }
2938 
2939 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_FP_TO_XINT(SDNode *N) {
2940   SDValue Op = N->getOperand(0);
2941   SDLoc dl(N);
2942 
2943   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), Op.getValueType());
2944 
2945   Op = GetSoftPromotedHalf(Op);
2946 
2947   SDValue Res = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op);
2948 
2949   return DAG.getNode(N->getOpcode(), dl, N->getValueType(0), Res);
2950 }
2951 
2952 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_FP_TO_XINT_SAT(SDNode *N) {
2953   SDValue Op = N->getOperand(0);
2954   SDLoc dl(N);
2955 
2956   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), Op.getValueType());
2957 
2958   Op = GetSoftPromotedHalf(Op);
2959 
2960   SDValue Res = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op);
2961 
2962   return DAG.getNode(N->getOpcode(), dl, N->getValueType(0), Res,
2963                      N->getOperand(1));
2964 }
2965 
2966 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_SELECT_CC(SDNode *N,
2967                                                       unsigned OpNo) {
2968   assert(OpNo == 0 && "Can only soften the comparison values");
2969   SDValue Op0 = N->getOperand(0);
2970   SDValue Op1 = N->getOperand(1);
2971   SDLoc dl(N);
2972 
2973   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), Op0.getValueType());
2974 
2975   Op0 = GetSoftPromotedHalf(Op0);
2976   Op1 = GetSoftPromotedHalf(Op1);
2977 
2978   // Promote to the larger FP type.
2979   Op0 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op0);
2980   Op1 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op1);
2981 
2982   return DAG.getNode(ISD::SELECT_CC, SDLoc(N), N->getValueType(0), Op0, Op1,
2983                      N->getOperand(2), N->getOperand(3), N->getOperand(4));
2984 }
2985 
2986 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_SETCC(SDNode *N) {
2987   SDValue Op0 = N->getOperand(0);
2988   SDValue Op1 = N->getOperand(1);
2989   ISD::CondCode CCCode = cast<CondCodeSDNode>(N->getOperand(2))->get();
2990   SDLoc dl(N);
2991 
2992   EVT NVT = TLI.getTypeToTransformTo(*DAG.getContext(), Op0.getValueType());
2993 
2994   Op0 = GetSoftPromotedHalf(Op0);
2995   Op1 = GetSoftPromotedHalf(Op1);
2996 
2997   // Promote to the larger FP type.
2998   Op0 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op0);
2999   Op1 = DAG.getNode(ISD::FP16_TO_FP, dl, NVT, Op1);
3000 
3001   return DAG.getSetCC(SDLoc(N), N->getValueType(0), Op0, Op1, CCCode);
3002 }
3003 
3004 SDValue DAGTypeLegalizer::SoftPromoteHalfOp_STORE(SDNode *N, unsigned OpNo) {
3005   assert(OpNo == 1 && "Can only soften the stored value!");
3006   StoreSDNode *ST = cast<StoreSDNode>(N);
3007   SDValue Val = ST->getValue();
3008   SDLoc dl(N);
3009 
3010   assert(!ST->isTruncatingStore() && "Unexpected truncating store.");
3011   SDValue Promoted = GetSoftPromotedHalf(Val);
3012   return DAG.getStore(ST->getChain(), dl, Promoted, ST->getBasePtr(),
3013                       ST->getMemOperand());
3014 }
3015