Skip to content

Commit 08ba37e

Browse files
RichBarton-Armbryanpkc
authored andcommitted
[driver] Pass LLVM target_features to flang
Port commit 64bf2a6 to LLVM 16 and resolve merge conflicts. The original commit message follows: Pass LLVM target features (-mattr strings) to flang to embed in generated .ll files. For normal compilation this won't make much difference as the attributes are passed to clang after flang2 and can be applied there but this is crucial to enable LTO with flang as clang will not apply the attributes when building the flang2 output. libLTO will need to read these out of the object files to apply them. Signed-off-by: Richard Barton <[email protected]>
1 parent f37d2ec commit 08ba37e

File tree

4 files changed

+64
-7
lines changed

4 files changed

+64
-7
lines changed

clang/lib/Driver/ToolChains/ClassicFlang.cpp

Lines changed: 25 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,8 @@ class ClassicFlangMacroBuilder : public MacroBuilder {
6060
void ClassicFlang::ConstructJob(Compilation &C, const JobAction &JA,
6161
const InputInfo &Output, const InputInfoList &Inputs,
6262
const ArgList &Args, const char *LinkingOutput) const {
63+
const Driver &D = getToolChain().getDriver();
64+
const llvm::Triple &Triple = getToolChain().getEffectiveTriple();
6365
ArgStringList CommonCmdArgs;
6466
ArgStringList UpperCmdArgs;
6567
ArgStringList LowerCmdArgs;
@@ -374,13 +376,13 @@ void ClassicFlang::ConstructJob(Compilation &C, const JobAction &JA,
374376

375377
// -Mipa has no effect
376378
if (Arg *A = Args.getLastArg(options::OPT_Mipa)) {
377-
getToolChain().getDriver().Diag(diag::warn_drv_clang_unsupported)
379+
D.Diag(diag::warn_drv_clang_unsupported)
378380
<< A->getAsString(Args);
379381
}
380382

381383
// -Minline has no effect
382384
if (Arg *A = Args.getLastArg(options::OPT_Minline_on)) {
383-
getToolChain().getDriver().Diag(diag::warn_drv_clang_unsupported)
385+
D.Diag(diag::warn_drv_clang_unsupported)
384386
<< A->getAsString(Args);
385387
}
386388

@@ -654,14 +656,14 @@ void ClassicFlang::ConstructJob(Compilation &C, const JobAction &JA,
654656
// Use clang's predefined macros
655657
DiagnosticsEngine DE(new DiagnosticIDs(), new DiagnosticOptions, new IgnoringDiagConsumer());
656658
std::shared_ptr<clang::TargetOptions> TO = std::make_shared<clang::TargetOptions>();
657-
TO->Triple = getToolChain().getEffectiveTriple().getTriple();
659+
TO->Triple = Triple.getTriple();
658660
std::shared_ptr<TargetInfo> TI(clang::TargetInfo::CreateTargetInfo(DE, TO));
659661
std::string PredefineBuffer;
660662
llvm::raw_string_ostream Predefines(PredefineBuffer);
661663
ClassicFlangMacroBuilder Builder(UpperCmdArgs, Args, Predefines);
662664

663665
LangOptions LO;
664-
VersionTuple VT = getToolChain().computeMSVCVersion(&getToolChain().getDriver(), Args);
666+
VersionTuple VT = getToolChain().computeMSVCVersion(&D, Args);
665667
if (!VT.empty()) {
666668
// Set the MSCompatibility version. Subminor version has 5 decimal digits.
667669
// Minor and major versions have 2 decimal digits each.
@@ -694,7 +696,7 @@ void ClassicFlang::ConstructJob(Compilation &C, const JobAction &JA,
694696
DefineTypeSize("__LONG_MAX__", TargetInfo::SignedLong, *TI, Builder);
695697

696698
// Add additional predefined macros
697-
switch (getToolChain().getEffectiveTriple().getArch()) {
699+
switch (Triple.getArch()) {
698700
case llvm::Triple::aarch64:
699701
UpperCmdArgs.push_back("-def"); UpperCmdArgs.push_back("__ARM_ARCH__=8");
700702
break;
@@ -788,7 +790,7 @@ void ClassicFlang::ConstructJob(Compilation &C, const JobAction &JA,
788790
Arg->claim();
789791
UpperCmdArgs.push_back("-extend");
790792
} else {
791-
getToolChain().getDriver().Diag(diag::err_drv_unsupported_fixed_line_length)
793+
D.Diag(diag::err_drv_unsupported_fixed_line_length)
792794
<< Arg->getAsString(Args);
793795
}
794796
}
@@ -832,7 +834,7 @@ void ClassicFlang::ConstructJob(Compilation &C, const JobAction &JA,
832834
} else if (Value == "95") { // Enable Fortran 2003 semantics
833835
UpperCmdArgs.push_back("-y"); // Unset XBIT
834836
} else {
835-
getToolChain().getDriver().Diag(diag::err_drv_invalid_allocatable_mode)
837+
D.Diag(diag::err_drv_invalid_allocatable_mode)
836838
<< A->getAsString(Args);
837839
}
838840
} else { // No argument passed
@@ -982,6 +984,22 @@ void ClassicFlang::ConstructJob(Compilation &C, const JobAction &JA,
982984
// Remove "noinline" attriblute
983985
LowerCmdArgs.push_back("-x"); LowerCmdArgs.push_back("183"); LowerCmdArgs.push_back("0x10");
984986

987+
// Add target features
988+
std::vector<StringRef> Features;
989+
std::string FeatureList = "";
990+
getTargetFeatureList(D, Triple, Args, UpperCmdArgs, false, Features);
991+
if (!Features.empty()) {
992+
for (unsigned I = 0, N = Features.size(); I < N; ++I) {
993+
StringRef Name = Features[I];
994+
FeatureList += Name.str();
995+
if (I < (N - 1))
996+
FeatureList += ',';
997+
}
998+
999+
LowerCmdArgs.push_back("-target_features");
1000+
LowerCmdArgs.push_back(Args.MakeArgString(FeatureList));
1001+
}
1002+
9851003
// Set a -x flag for second part of Fortran frontend
9861004
for (Arg *A : Args.filtered(options::OPT_Mx_EQ)) {
9871005
A->claim();

clang/lib/Driver/ToolChains/CommonArgs.cpp

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -765,10 +765,18 @@ static void getWebAssemblyTargetFeatures(const Driver &D,
765765
options::OPT_m_wasm_Features_Group);
766766
}
767767

768+
#ifndef ENABLE_CLASSIC_FLANG
768769
void tools::getTargetFeatures(const Driver &D, const llvm::Triple &Triple,
769770
const ArgList &Args, ArgStringList &CmdArgs,
770771
bool ForAS, bool IsAux) {
771772
std::vector<StringRef> Features;
773+
#else
774+
void tools::getTargetFeatureList(const Driver &D,
775+
const llvm::Triple &Triple,
776+
const ArgList &Args, ArgStringList &CmdArgs,
777+
bool ForAS,
778+
std::vector<StringRef> &Features) {
779+
#endif
772780
switch (Triple.getArch()) {
773781
default:
774782
break;
@@ -843,6 +851,15 @@ void tools::getTargetFeatures(const Driver &D, const llvm::Triple &Triple,
843851
loongarch::getLoongArchTargetFeatures(D, Triple, Args, Features);
844852
break;
845853
}
854+
#ifdef ENABLE_CLASSIC_FLANG
855+
}
856+
857+
void tools::getTargetFeatures(const Driver &D, const llvm::Triple &Triple,
858+
const ArgList &Args, ArgStringList &CmdArgs,
859+
bool ForAS, bool IsAux) {
860+
std::vector<StringRef> Features;
861+
getTargetFeatureList(D, Triple, Args, CmdArgs, ForAS, Features);
862+
#endif
846863

847864
for (auto Feature : unifyTargetFeatures(Features)) {
848865
CmdArgs.push_back(IsAux ? "-aux-target-feature" : "-target-feature");

clang/lib/Driver/ToolChains/CommonArgs.h

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -174,6 +174,17 @@ void AddTargetFeature(const llvm::opt::ArgList &Args,
174174
std::string getCPUName(const Driver &D, const llvm::opt::ArgList &Args,
175175
const llvm::Triple &T, bool FromAs = false);
176176

177+
#ifdef ENABLE_CLASSIC_FLANG
178+
// Helper function extracted from upstream getTargetFeatures. Classic Flang
179+
// uses this helper to render the target feature options for the Fortran
180+
// frontend.
181+
void getTargetFeatureList(const Driver &D,
182+
const llvm::Triple &Triple,
183+
const llvm::opt::ArgList &Args,
184+
llvm::opt::ArgStringList &CmdArgs,
185+
bool ForAS, std::vector<StringRef> &Features);
186+
#endif
187+
177188
void getTargetFeatures(const Driver &D, const llvm::Triple &Triple,
178189
const llvm::opt::ArgList &Args,
179190
llvm::opt::ArgStringList &CmdArgs, bool ForAS,
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
// REQUIRES: aarch64-registered-target
2+
// REQUIRES: classic_flang
3+
// RUN: %flang -### -target aarch64-linux-gnu -march=armv8-a -c %s 2>&1 | FileCheck --check-prefix=CHECK-ATTRS-NEON %s
4+
// RUN: %flang -### -target aarch64-linux-gnu -march=armv8-a+sve -c %s 2>&1 | FileCheck --check-prefix=CHECK-ATTRS-SVE %s
5+
// RUN: %flang -### -target aarch64-linux-gnu -march=armv8-a+nosve -c %s 2>&1 | FileCheck --check-prefix=CHECK-ATTRS-NOSVE %s
6+
// CHECK-ATTRS-NEON: "{{.*}}flang2"
7+
// CHECK-ATTRS-NEON-SAME: "-target_features" "+neon,+v8a
8+
// CHECK-ATTRS-SVE: "{{.*}}flang2"
9+
// CHECK-ATTRS-SVE-SAME: "-target_features" "+neon,+v8a,+sve
10+
// CHECK-ATTRS-NOSVE: "{{.*}}flang2"
11+
// CHECK-ATTRS-NOSVE-SAME: "-target_features" "+neon,+v8a,-sve

0 commit comments

Comments
 (0)