[Git][ghc/ghc][master] Generate LLVM min/max bound policy via Hadrian

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Feb 8 11:39:39 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00
Generate LLVM min/max bound policy via Hadrian

Per #23966, I want the top-level configure to only generate
configuration data for Hadrian, not do any "real" tasks on its own.
This is part of that effort --- one less file generated by it.

(It is still done with a `.in` file, so in a future world non-Hadrian
also can easily create this file.)

Split modules:

- GHC.CmmToLlvm.Config
- GHC.CmmToLlvm.Version
- GHC.CmmToLlvm.Version.Bounds
- GHC.CmmToLlvm.Version.Type

This also means we can get rid of the silly `unused.h` introduced in
!6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge.

Part of #23966

- - - - -


16 changed files:

- .gitignore
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/Config.hs
- + compiler/GHC/CmmToLlvm/Version.hs
- + compiler/GHC/CmmToLlvm/Version/Bounds.hs.in
- + compiler/GHC/CmmToLlvm/Version/Type.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/SysTools/Tasks.hs
- − compiler/ghc-llvm-version.h.in
- compiler/ghc.cabal.in
- configure.ac
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Lint.hs
- hadrian/src/Rules/SourceDist.hs


Changes:

=====================================
.gitignore
=====================================
@@ -113,7 +113,7 @@ _darcs/
 /compiler/FunTypes.h
 /compiler/MachRegs.h
 /compiler/MachRegs
-/compiler/ghc-llvm-version.h
+/compiler/GHC/CmmToLlvm/Version/Bounds.hs
 /compiler/ghc.cabal
 /compiler/ghc.cabal.old
 /distrib/configure.ac
@@ -185,8 +185,6 @@ _darcs/
 /linter.log
 /mk/are-validating.mk
 /mk/build.mk
-/mk/unused.h
-/mk/unused.h.in
 /mk/config.mk
 /mk/config.mk.old
 /mk/system-cxx-std-lib-1.0.conf


=====================================
compiler/GHC/CmmToLlvm.hs
=====================================
@@ -21,6 +21,7 @@ import GHC.CmmToLlvm.Data
 import GHC.CmmToLlvm.Ppr
 import GHC.CmmToLlvm.Regs
 import GHC.CmmToLlvm.Mangler
+import GHC.CmmToLlvm.Version
 
 import GHC.StgToCmm.CgUtils ( fixStgRegisters )
 import GHC.Cmm


=====================================
compiler/GHC/CmmToLlvm/Base.hs
=====================================
@@ -41,6 +41,7 @@ import GHC.Utils.Panic
 import GHC.Llvm
 import GHC.CmmToLlvm.Regs
 import GHC.CmmToLlvm.Config
+import GHC.CmmToLlvm.Version
 
 import GHC.Cmm.CLabel
 import GHC.Platform.Regs ( activeStgRegs, globalRegMaybe )


=====================================
compiler/GHC/CmmToLlvm/Config.hs
=====================================
@@ -1,34 +1,20 @@
-{-# LANGUAGE CPP #-}
-
 -- | Llvm code generator configuration
 module GHC.CmmToLlvm.Config
   ( LlvmCgConfig(..)
   , LlvmConfig(..)
   , LlvmTarget(..)
   , initLlvmConfig
-  -- * LLVM version
-  , LlvmVersion(..)
-  , supportedLlvmVersionLowerBound
-  , supportedLlvmVersionUpperBound
-  , parseLlvmVersion
-  , llvmVersionSupported
-  , llvmVersionStr
-  , llvmVersionList
   )
 where
 
-#include "ghc-llvm-version.h"
-
 import GHC.Prelude
 import GHC.Platform
 
 import GHC.Utils.Outputable
 import GHC.Settings.Utils
 import GHC.Utils.Panic
+import GHC.CmmToLlvm.Version.Type (LlvmVersion)
 
-import Data.Char (isDigit)
-import Data.List (intercalate)
-import qualified Data.List.NonEmpty as NE
 import System.FilePath
 
 data LlvmCgConfig = LlvmCgConfig
@@ -94,43 +80,3 @@ data LlvmConfig = LlvmConfig
   { llvmTargets :: [(String, LlvmTarget)]
   , llvmPasses  :: [(Int, String)]
   }
-
-
----------------------------------------------------------
--- LLVM version
----------------------------------------------------------
-
-newtype LlvmVersion = LlvmVersion { llvmVersionNE :: NE.NonEmpty Int }
-  deriving (Eq, Ord)
-
-parseLlvmVersion :: String -> Maybe LlvmVersion
-parseLlvmVersion =
-    fmap LlvmVersion . NE.nonEmpty . go [] . dropWhile (not . isDigit)
-  where
-    go vs s
-      | null ver_str
-      = reverse vs
-      | '.' : rest' <- rest
-      = go (read ver_str : vs) rest'
-      | otherwise
-      = reverse (read ver_str : vs)
-      where
-        (ver_str, rest) = span isDigit s
-
--- | The (inclusive) lower bound on the LLVM Version that is currently supported.
-supportedLlvmVersionLowerBound :: LlvmVersion
-supportedLlvmVersionLowerBound = LlvmVersion (sUPPORTED_LLVM_VERSION_MIN NE.:| [])
-
--- | The (not-inclusive) upper bound  bound on the LLVM Version that is currently supported.
-supportedLlvmVersionUpperBound :: LlvmVersion
-supportedLlvmVersionUpperBound = LlvmVersion (sUPPORTED_LLVM_VERSION_MAX NE.:| [])
-
-llvmVersionSupported :: LlvmVersion -> Bool
-llvmVersionSupported v =
-  v >= supportedLlvmVersionLowerBound && v < supportedLlvmVersionUpperBound
-
-llvmVersionStr :: LlvmVersion -> String
-llvmVersionStr = intercalate "." . map show . llvmVersionList
-
-llvmVersionList :: LlvmVersion -> [Int]
-llvmVersionList = NE.toList . llvmVersionNE


=====================================
compiler/GHC/CmmToLlvm/Version.hs
=====================================
@@ -0,0 +1,43 @@
+module GHC.CmmToLlvm.Version
+  ( LlvmVersion(..)
+  , supportedLlvmVersionLowerBound
+  , supportedLlvmVersionUpperBound
+  , parseLlvmVersion
+  , llvmVersionSupported
+  , llvmVersionStr
+  , llvmVersionList
+  )
+where
+
+import GHC.Prelude
+
+import GHC.CmmToLlvm.Version.Type
+import GHC.CmmToLlvm.Version.Bounds
+
+import Data.Char (isDigit)
+import Data.List (intercalate)
+import qualified Data.List.NonEmpty as NE
+
+parseLlvmVersion :: String -> Maybe LlvmVersion
+parseLlvmVersion =
+    fmap LlvmVersion . NE.nonEmpty . go [] . dropWhile (not . isDigit)
+  where
+    go vs s
+      | null ver_str
+      = reverse vs
+      | '.' : rest' <- rest
+      = go (read ver_str : vs) rest'
+      | otherwise
+      = reverse (read ver_str : vs)
+      where
+        (ver_str, rest) = span isDigit s
+
+llvmVersionSupported :: LlvmVersion -> Bool
+llvmVersionSupported v =
+  v >= supportedLlvmVersionLowerBound && v < supportedLlvmVersionUpperBound
+
+llvmVersionStr :: LlvmVersion -> String
+llvmVersionStr = intercalate "." . map show . llvmVersionList
+
+llvmVersionList :: LlvmVersion -> [Int]
+llvmVersionList = NE.toList . llvmVersionNE


=====================================
compiler/GHC/CmmToLlvm/Version/Bounds.hs.in
=====================================
@@ -0,0 +1,19 @@
+module GHC.CmmToLlvm.Version.Bounds
+  ( supportedLlvmVersionLowerBound
+  , supportedLlvmVersionUpperBound
+  )
+where
+
+import GHC.Prelude ()
+
+import GHC.CmmToLlvm.Version.Type
+
+import qualified Data.List.NonEmpty as NE
+
+-- | The (inclusive) lower bound on the LLVM Version that is currently supported.
+supportedLlvmVersionLowerBound :: LlvmVersion
+supportedLlvmVersionLowerBound = LlvmVersion (@LlvmMinVersion@ NE.:| [])
+
+-- | The (not-inclusive) upper bound  bound on the LLVM Version that is currently supported.
+supportedLlvmVersionUpperBound :: LlvmVersion
+supportedLlvmVersionUpperBound = LlvmVersion (@LlvmMaxVersion@ NE.:| [])


=====================================
compiler/GHC/CmmToLlvm/Version/Type.hs
=====================================
@@ -0,0 +1,11 @@
+module GHC.CmmToLlvm.Version.Type
+  ( LlvmVersion(..)
+  )
+where
+
+import GHC.Prelude
+
+import qualified Data.List.NonEmpty as NE
+
+newtype LlvmVersion = LlvmVersion { llvmVersionNE :: NE.NonEmpty Int }
+  deriving (Eq, Ord)


=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -15,7 +15,7 @@ where
 import GHC.Prelude
 import GHC.Driver.Session
 import GHC.Driver.Backend
-import GHC.CmmToLlvm.Config
+import GHC.CmmToLlvm.Version
 import GHC.Platform
 import GHC.Platform.ArchOS
 


=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -12,7 +12,7 @@ module GHC.SysTools.Tasks where
 import GHC.Prelude
 import GHC.ForeignSrcLang
 
-import GHC.CmmToLlvm.Config (LlvmVersion, llvmVersionStr, supportedLlvmVersionUpperBound, parseLlvmVersion, supportedLlvmVersionLowerBound)
+import GHC.CmmToLlvm.Version (LlvmVersion, llvmVersionStr, supportedLlvmVersionUpperBound, parseLlvmVersion, supportedLlvmVersionLowerBound)
 
 import GHC.Settings
 


=====================================
compiler/ghc-llvm-version.h.in deleted
=====================================
@@ -1,10 +0,0 @@
-#if !defined(__GHC_LLVM_VERSION_H__)
-#define __GHC_LLVM_VERSION_H__
-
-/* The maximum supported LLVM version number */
-#undef sUPPORTED_LLVM_VERSION_MAX
-
-/* The minimum supported LLVM version number */
-#undef sUPPORTED_LLVM_VERSION_MIN
-
-#endif /* __GHC_LLVM_VERSION_H__ */


=====================================
compiler/ghc.cabal.in
=====================================
@@ -47,7 +47,6 @@ extra-source-files:
     MachRegs/s390x.h
     MachRegs/wasm32.h
     MachRegs/x86.h
-    ghc-llvm-version.h
 
 
 custom-setup
@@ -92,7 +91,6 @@ Library
               Bytecodes.h
               ClosureTypes.h
               FunTypes.h
-              ghc-llvm-version.h
 
     if flag(build-tool-depends)
       build-tool-depends: alex:alex >= 3.2.6, happy:happy >= 1.20.0, genprimopcode:genprimopcode, deriveConstants:deriveConstants
@@ -319,6 +317,9 @@ Library
         GHC.CmmToLlvm.Mangler
         GHC.CmmToLlvm.Ppr
         GHC.CmmToLlvm.Regs
+        GHC.CmmToLlvm.Version
+        GHC.CmmToLlvm.Version.Bounds
+        GHC.CmmToLlvm.Version.Type
         GHC.Cmm.Dominators
         GHC.Cmm.Reducibility
         GHC.Cmm.Type


=====================================
configure.ac
=====================================
@@ -80,18 +80,6 @@ dnl     #define SIZEOF_CHAR 0
 dnl   recently.
 AC_PREREQ([2.69])
 
-# -------------------------------------------------------------------------
-# Prepare to generate the following header files
-#
-
-dnl so the next header, which is manually maintained, doesn't get
-dnl overwritten by an autogenerated header. Once we have no more
-dnl `AC_CONFIG_HEADER` calls (issue #23966) we can delete all mention
-dnl of `mk/unused.h`.
-AC_CONFIG_HEADER(mk/unused.h)
-# This one is manually maintained.
-AC_CONFIG_HEADER(compiler/ghc-llvm-version.h)
-
 # No, semi-sadly, we don't do `--srcdir'...
 if test x"$srcdir" != 'x.' ; then
     echo "This configuration does not support the \`--srcdir' option.."
@@ -507,10 +495,6 @@ LlvmMinVersion=13  # inclusive
 LlvmMaxVersion=16 # not inclusive
 AC_SUBST([LlvmMinVersion])
 AC_SUBST([LlvmMaxVersion])
-sUPPORTED_LLVM_VERSION_MIN=$(echo \($LlvmMinVersion\) | sed 's/\./,/')
-sUPPORTED_LLVM_VERSION_MAX=$(echo \($LlvmMaxVersion\) | sed 's/\./,/')
-AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION_MIN], ${sUPPORTED_LLVM_VERSION_MIN}, [The minimum supported LLVM version number])
-AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION_MAX], ${sUPPORTED_LLVM_VERSION_MAX}, [The maximum supported LLVM version number])
 
 ConfiguredEmsdkVersion="${EmsdkVersion}"
 AC_SUBST([ConfiguredEmsdkVersion])


=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -125,6 +125,17 @@ biModules pd = go [ comp | comp@(bi,_,_,_) <-
     go [x] = x
     go _   = error "Cannot handle more than one buildinfo yet."
 
+-- Extra files needed prior to configuring.
+--
+-- These should be "static" source files: ones whose contents do not
+-- change based on the build configuration, and ones which are therefore
+-- also safe to include in sdists for package-level builds.
+--
+-- Put another way, while Hadrian knows these are generated, Cabal
+-- should just think they are regular source files.
+extraPreConfigureDeps :: [String]
+extraPreConfigureDeps = ["compiler/GHC/CmmToLlvm/Version/Bounds.hs"]
+
 -- TODO: Track command line arguments and package configuration flags.
 -- | Configure a package using the Cabal library by collecting all the command
 -- line arguments (to be passed to the setup script) and package configuration
@@ -141,7 +152,7 @@ configurePackage context at Context {..} = do
     -- We'll need those packages in our package database.
     deps <- sequence [ pkgConfFile (context { package = pkg })
                      | pkg <- depPkgs, pkg `elem` stagePkgs ]
-    need deps
+    need $ extraPreConfigureDeps ++ deps
 
     -- Figure out what hooks we need.
     let configureFile = replaceFileName (pkgCabalFile package) "configure"


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -71,9 +71,12 @@ rtsDependencies = do
 
 compilerDependencies :: Expr [FilePath]
 compilerDependencies = do
+    let fixed = ("compiler" -/-) <$>
+                  [ "GHC/CmmToLlvm/Version/Bounds.hs"
+                  ]
     stage   <- getStage
     ghcPath <- expr $ buildPath (vanillaContext stage compiler)
-    pure $ (ghcPath -/-) <$>
+    let buildSpecific = (ghcPath -/-) <$>
                   [ "primop-code-size.hs-incl"
                   , "primop-commutable.hs-incl"
                   , "primop-data-decl.hs-incl"
@@ -94,6 +97,7 @@ compilerDependencies = do
                   , "GHC/Platform/Constants.hs"
                   , "GHC/Settings/Config.hs"
                   ]
+    pure $ fixed ++ buildSpecific
 
 generatedDependencies :: Expr [FilePath]
 generatedDependencies = do
@@ -332,6 +336,10 @@ templateRules = do
     , interpolateSetting "LlvmMinVersion" LlvmMinVersion
     , interpolateSetting "LlvmMaxVersion" LlvmMaxVersion
     ]
+  templateRule "compiler/GHC/CmmToLlvm/Version/Bounds.hs" $ mconcat
+    [ interpolateVar "LlvmMinVersion" $ replaceEq '.' ',' <$> setting LlvmMinVersion
+    , interpolateVar "LlvmMaxVersion" $ replaceEq '.' ',' <$> setting LlvmMaxVersion
+    ]
 
 
 -- Generators


=====================================
hadrian/src/Rules/Lint.hs
=====================================
@@ -92,7 +92,8 @@ compiler = do
   let compilerDir    = "compiler"
   let ghcautoconf    = stage1RtsInc </> "ghcautoconf.h"
   let ghcplatform    = stage1RtsInc </> "ghcplatform.h"
-  need $ mconcat [[ghcautoconf, ghcplatform], hsIncls stage1Compiler, [machDeps]]
+  let ghcLlvmVersion = compilerDir </> "GHC/CmmToLlvm/Version/Bounds.hs"
+  need $ mconcat [[ghcautoconf, ghcplatform, ghcLlvmVersion], hsIncls stage1Compiler, [machDeps]]
   let includeDirs =
         [ stage1RtsInc
         , compilerDir


=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -156,7 +156,6 @@ prepareTree dest = do
       , pkgPath terminfo -/- "configure"
       , "configure"
       , "aclocal.m4"
-      , "mk" -/- "unused.h.in"
       ]
 
     copyAlexHappyFiles =



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c37931b35c47dfe0ac1acea25943f3af2396e7fd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c37931b35c47dfe0ac1acea25943f3af2396e7fd
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/20240208/35d29049/attachment-0001.html>


More information about the ghc-commits mailing list