[Git][ghc/ghc][master] driver: bail out when -fllvm is passed to GHC not configured with LLVM
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Oct 11 07:53:40 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM
This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.
Fixes #25011
Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>
- - - - -
5 changed files:
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Types/Error/Codes.hs
- testsuite/tests/diagnostic-codes/codes.stdout
Changes:
=====================================
compiler/GHC/Driver/Errors/Ppr.hs
=====================================
@@ -35,6 +35,7 @@ import GHC.HsToCore.Errors.Types (DsMessage)
import GHC.Iface.Errors.Types
import GHC.Tc.Errors.Ppr () -- instance Diagnostic TcRnMessage
import GHC.Iface.Errors.Ppr () -- instance Diagnostic IfaceMessage
+import GHC.CmmToLlvm.Version (llvmVersionStr, supportedLlvmVersionLowerBound, supportedLlvmVersionUpperBound)
--
-- Suggestions
@@ -268,6 +269,14 @@ instance Diagnostic DriverMessage where
mkSimpleDecorated $
vcat [ text "Unexpected backpack instantiation in dependency graph while constructing Makefile:"
, nest 2 $ ppr node ]
+ DriverNoConfiguredLLVMToolchain ->
+ mkSimpleDecorated $
+ text "GHC was not configured with a supported LLVM toolchain" $$
+ text ("Make sure you have installed LLVM between ["
+ ++ llvmVersionStr supportedLlvmVersionLowerBound
+ ++ " and "
+ ++ llvmVersionStr supportedLlvmVersionUpperBound
+ ++ ") and reinstall GHC to make -fllvm work")
diagnosticReason = \case
DriverUnknownMessage m
@@ -337,6 +346,8 @@ instance Diagnostic DriverMessage where
-> ErrorWithoutFlag
DriverInstantiationNodeInDependencyGeneration {}
-> ErrorWithoutFlag
+ DriverNoConfiguredLLVMToolchain
+ -> ErrorWithoutFlag
diagnosticHints = \case
DriverUnknownMessage m
@@ -408,5 +419,7 @@ instance Diagnostic DriverMessage where
-> noHints
DriverInstantiationNodeInDependencyGeneration {}
-> noHints
+ DriverNoConfiguredLLVMToolchain
+ -> noHints
diagnosticCode = constructorCode
=====================================
compiler/GHC/Driver/Errors/Types.hs
=====================================
@@ -402,6 +402,14 @@ data DriverMessage where
Backpack 'InstantiationNode's. -}
DriverInstantiationNodeInDependencyGeneration :: InstantiatedUnit -> DriverMessage
+ {-| DriverNoConfiguredLLVMToolchain is an error that occurs if there is no
+ LLVM toolchain configured but -fllvm is passed as an option to the compiler.
+
+ Test cases: None.
+
+ -}
+ DriverNoConfiguredLLVMToolchain :: DriverMessage
+
deriving instance Generic DriverMessage
data DriverMessageOpts =
=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -19,7 +19,6 @@ import GHC.Settings
import GHC.SysTools.Process
import GHC.Driver.Session
-
import GHC.Utils.Exception as Exception
import GHC.Utils.Error
import GHC.Utils.Outputable
@@ -28,10 +27,16 @@ import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Utils.Panic
+import Control.Monad
import Data.List (tails, isPrefixOf)
import Data.Maybe (fromMaybe)
import System.IO
import System.Process
+import GHC.Driver.Config.Diagnostic
+import GHC.Driver.Errors
+import GHC.Driver.Errors.Types (GhcMessage(..), DriverMessage (DriverNoConfiguredLLVMToolchain))
+import GHC.Driver.CmdLine (warnsToMessages)
+import GHC.Types.SrcLoc (noLoc)
{-
************************************************************************
@@ -277,12 +282,26 @@ runEmscripten logger dflags args = traceSystoolCommand logger "emcc" $ do
figureLlvmVersion :: Logger -> DynFlags -> IO (Maybe LlvmVersion)
figureLlvmVersion logger dflags = traceSystoolCommand logger "llc" $ do
let (pgm,opts) = pgm_lc dflags
+ diag_opts = initDiagOpts dflags
args = filter notNull (map showOpt opts)
-- we grab the args even though they should be useless just in
-- case the user is using a customised 'llc' that requires some
-- of the options they've specified. llc doesn't care what other
-- options are specified when '-version' is used.
args' = args ++ ["-version"]
+ -- Since !12001, when GHC is not configured with llc/opt with
+ -- supported version range, configure script will leave llc/opt
+ -- commands as blank in settings. In this case, we should bail out
+ -- with a proper error, see #25011.
+ --
+ -- Note that this does not make the -Wunsupported-llvm-version
+ -- warning logic redundant! Power users might want to use
+ -- -pgmlc/-pgmlo to override llc/opt locations to test LLVM outside
+ -- officially supported version range, and the driver will produce
+ -- the warning and carry on code generation.
+ when (null pgm) $
+ printOrThrowDiagnostics logger (initPrintConfig dflags) diag_opts
+ (GhcDriverMessage <$> warnsToMessages diag_opts [noLoc DriverNoConfiguredLLVMToolchain])
catchIO (do
(pin, pout, perr, p) <- runInteractiveProcess pgm args'
Nothing Nothing
@@ -360,4 +379,3 @@ runWindres logger dflags args = traceSystoolCommand logger "windres" $ do
opts = map Option (getOpts dflags opt_windres)
mb_env <- getGccEnv cc_args
runSomethingFiltered logger id "Windres" windres (opts ++ args) Nothing mb_env
-
=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -323,6 +323,7 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "DriverDeprecatedFlag" = 53692
GhcDiagnosticCode "DriverModuleGraphCycle" = 92213
GhcDiagnosticCode "DriverInstantiationNodeInDependencyGeneration" = 74284
+ GhcDiagnosticCode "DriverNoConfiguredLLVMToolchain" = 66599
-- Constraint solver diagnostic codes
GhcDiagnosticCode "BadTelescope" = 97739
=====================================
testsuite/tests/diagnostic-codes/codes.stdout
=====================================
@@ -42,6 +42,7 @@
[GHC-37141] is untested (constructor = DriverCannotLoadInterfaceFile)
[GHC-29747] is untested (constructor = DriverMissingSafeHaskellMode)
[GHC-74284] is untested (constructor = DriverInstantiationNodeInDependencyGeneration)
+[GHC-66599] is untested (constructor = DriverNoConfiguredLLVMToolchain)
[GHC-06200] is untested (constructor = BlockedEquality)
[GHC-81325] is untested (constructor = ExpectingMoreArguments)
[GHC-78125] is untested (constructor = AmbiguityPreventsSolvingCt)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2338a971ce45ce7bc6ba2711e40966ec5ff12359
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2338a971ce45ce7bc6ba2711e40966ec5ff12359
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241011/0f8c6d43/attachment-0001.html>
More information about the ghc-commits
mailing list