Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC Commits: 39826302 by Zubin Duggal at 2025-07-23T16:12:05+05:30 bump deepseq to 1.5.2.0 - - - - - f797deee by Zubin Duggal at 2025-07-23T16:12:05+05:30 bump os-string to 2.0.7 - - - - - b2708200 by Zubin Duggal at 2025-07-23T16:12:05+05:30 bump process to 1.6.26.1 - - - - - 8801d8e4 by Zubin Duggal at 2025-07-23T16:12:05+05:30 bump unix to 2.8.7.0 - - - - - e11f8b84 by Jens Petersen at 2025-07-23T16:12:06+05:30 9.10 hadrian can build with Cabal-3.12.1 fixes #25605 (cherry picked from commit 07f17b6ed1bb0ba7134ee8dfd992036e97552c94) - - - - - 13 changed files: - hadrian/hadrian.cabal - hadrian/src/Context.hs - hadrian/src/Hadrian/Haskell/Cabal/Parse.hs - hadrian/src/Hadrian/Haskell/Cabal/Type.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Settings/Builders/Ghc.hs - libraries/deepseq - libraries/os-string - libraries/process - libraries/unix Changes: ===================================== hadrian/hadrian.cabal ===================================== @@ -152,7 +152,7 @@ executable hadrian , TypeOperators other-extensions: MultiParamTypeClasses , TypeFamilies - build-depends: Cabal >= 3.10 && < 3.11 + build-depends: Cabal (>= 3.10 && < 3.11) || (>= 3.12.1 && < 3.13) , base >= 4.11 && < 5 , bytestring >= 0.10 && < 0.13 , containers >= 0.5 && < 0.8 ===================================== hadrian/src/Context.hs ===================================== @@ -9,7 +9,7 @@ module Context ( contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir, pkgHaddockFile, pkgRegisteredLibraryFile, pkgRegisteredLibraryFileName, pkgLibraryFile, pkgGhciLibraryFile, - pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir, + pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir, distDynDir, haddockStatsFilesDir ) where @@ -21,6 +21,8 @@ import Hadrian.Haskell.Cabal import Oracles.Setting import GHC.Toolchain.Target (Target(..)) import GHC.Platform.ArchOS +import Hadrian.Oracles.Cabal +import Hadrian.Haskell.Cabal.Type -- | Most targets are built only one way, hence the notion of 'vanillaContext'. vanillaContext :: Stage -> Package -> Context @@ -62,12 +64,15 @@ libPath Context {..} = buildRoot <&> (-/- (stageString stage -/- "lib")) -- -- We preform some renaming to accommodate Cabal's slightly different naming -- conventions (see 'cabalOsString' and 'cabalArchString'). -distDir :: Stage -> Action FilePath -distDir st = do - version <- ghcVersionStage st - targetOs <- cabalOsString . stringEncodeOS . archOS_OS . tgtArchOs <$> targetStage st - targetArch <- cabalArchString . stringEncodeArch . archOS_arch . tgtArchOs <$> targetStage st - return $ targetArch ++ "-" ++ targetOs ++ "-ghc-" ++ version +distDir :: Context -> Action FilePath +distDir c = do + cd <- readContextData c + return (contextLibdir cd) + +distDynDir :: Context -> Action FilePath +distDynDir c = do + cd <- readContextData c + return (contextDynLibdir cd) pkgFileName :: Context -> Package -> String -> String -> Action FilePath pkgFileName context package prefix suffix = do @@ -107,10 +112,11 @@ pkgRegisteredLibraryFile context@Context {..} = do libDir <- libPath context pkgId <- pkgUnitId stage package fileName <- pkgRegisteredLibraryFileName context - distDir <- distDir stage + distDir <- distDir context + distDynDir <- distDynDir context return $ if Dynamic `wayUnit` way - then libDir -/- distDir -/- fileName - else libDir -/- distDir -/- pkgId -/- fileName + then distDynDir -/- fileName + else distDir -/- fileName -- | Just the final filename portion of pkgRegisteredLibraryFile pkgRegisteredLibraryFileName :: Context -> Action FilePath ===================================== hadrian/src/Hadrian/Haskell/Cabal/Parse.hs ===================================== @@ -254,6 +254,7 @@ resolveContextData context@Context {..} = do pdi <- liftIO $ getHookedBuildInfo [pkgPath package, cPath -/- "build"] let pd' = C.updatePackageDescription pdi (C.localPkgDescr lbi) lbi' = lbi { C.localPkgDescr = pd' } + pkgDbPath <- packageDbPath (PackageDbLoc stage iplace) -- TODO: Get rid of deprecated 'externalPackageDeps' and drop -Wno-deprecations -- See: https://github.com/snowleopard/hadrian/issues/548 @@ -302,6 +303,8 @@ resolveContextData context@Context {..} = do | takeExtension fp `elem` [".cpp", ".cxx", ".c++"]= CppMain | otherwise = CMain + install_dirs = absoluteInstallDirs pd' lbi' (CopyToDb pkgDbPath) + main_src = fmap (first C.display) mainIs cdata = ContextData { dependencies = deps @@ -343,7 +346,10 @@ resolveContextData context@Context {..} = do , depLdOpts = forDeps Installed.ldOptions , buildGhciLib = C.withGHCiLib lbi' , frameworks = C.frameworks buildInfo - , packageDescription = pd' } + , packageDescription = pd' + , contextLibdir = libdir install_dirs + , contextDynLibdir = dynlibdir install_dirs + } in return cdata ===================================== hadrian/src/Hadrian/Haskell/Cabal/Type.hs ===================================== @@ -70,6 +70,10 @@ data ContextData = ContextData , buildGhciLib :: Bool , frameworks :: [String] , packageDescription :: PackageDescription + -- The location where normal library files go + , contextLibdir :: FilePath + -- The location where dynamic libraries go + , contextDynLibdir :: FilePath } deriving (Eq, Generic, Show, Typeable) instance Binary PackageData ===================================== hadrian/src/Rules/BinaryDist.hs ===================================== @@ -146,7 +146,7 @@ bindistRules = do phony "binary-dist-dir" $ do version <- setting ProjectVersion targetPlatform <- setting TargetPlatformFull - distDir <- Context.distDir Stage1 + distDir <- Context.distDir (vanillaContext Stage1 rts) rtsDir <- pkgUnitId Stage1 rts -- let rtsDir = "rts" ===================================== hadrian/src/Rules/CabalReinstall.hs ===================================== @@ -53,13 +53,11 @@ cabalBuildRules = do iserv_targets <- if cross then pure [] else iservBins need (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets))) - distDir <- Context.distDir Stage1 + distDir <- Context.distDir (vanillaContext Stage1 rts) rtsDir <- pkgUnitId Stage1 rts -- let rtsDir = "rts" - let ghcBuildDir = root -/- stageString Stage1 - rtsIncludeDir = ghcBuildDir -/- "lib" -/- distDir -/- rtsDir - -/- "include" + let rtsIncludeDir = distDir -/- "include" libdir <- liftIO . IO.makeAbsolute =<< stageLibPath Stage1 work_dir <- liftIO $ IO.makeAbsolute $ root -/- "stage-cabal" ===================================== hadrian/src/Rules/Register.hs ===================================== @@ -182,11 +182,12 @@ buildConfFinal rs context@Context {..} _conf = do -- -- so that if any change ends up modifying a library (but not its .conf -- file), we still rebuild things that depend on it. - dir <- (-/-) <$> libPath context <*> distDir stage + dir <- distDir context + dyndir <- distDynDir context pkgid <- pkgUnitId stage package files <- liftIO $ - (++) <$> getDirectoryFilesIO "." [dir -/- "*libHS"++pkgid++"*"] - <*> getDirectoryFilesIO "." [dir -/- pkgid -/- "**"] + (++) <$> getDirectoryFilesIO "." [dyndir -/- "*libHS"++pkgid++"*"] + <*> getDirectoryFilesIO "." [dir -/- "**"] produces files buildConfInplace :: [(Resource, Int)] -> Context -> FilePath -> Action () ===================================== hadrian/src/Rules/Rts.hs ===================================== @@ -154,10 +154,9 @@ needRtsSymLinks :: Stage -> Set.Set Way -> Action () needRtsSymLinks stage rtsWays = forM_ (Set.filter (wayUnit Dynamic) rtsWays) $ \ way -> do let ctx = Context stage rts way Final - libPath <- libPath ctx - distDir <- distDir stage + distDir <- distDynDir ctx rtsLibFile <- takeFileName <$> pkgLibraryFile ctx - need [removeRtsDummyVersion (libPath > distDir > rtsLibFile)] + need [removeRtsDummyVersion (distDir > rtsLibFile)] prefix, versionlessPrefix :: String versionlessPrefix = "libHSrts" ===================================== hadrian/src/Settings/Builders/Ghc.hs ===================================== @@ -99,8 +99,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do originPath <- dropFileName <$> getOutput context <- getContext libPath' <- expr (libPath context) - st <- getStage - distDir <- expr (Context.distDir st) + distPath <- expr (Context.distDynDir context) useSystemFfi <- expr (flag UseSystemFfi) buildPath <- getBuildPath @@ -112,7 +111,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do let dynamic = Dynamic `wayUnit` way - distPath = libPath' -/- distDir originToLibsDir = makeRelativeNoSysLink originPath distPath rpath -- Programs will end up in the bin dir ($ORIGIN) and will link to ===================================== libraries/deepseq ===================================== @@ -1 +1 @@ -Subproject commit 09aed1bf774f2f05c8b390539ce35adf5cd68c30 +Subproject commit 882f52f51854544a467babd8cb075e3271f5913e ===================================== libraries/os-string ===================================== @@ -1 +1 @@ -Subproject commit 6d31aafde2f7b8c3050ffee7dd9f658225cfd1a4 +Subproject commit 4b5efedcd2da9314edda80d973a44e67020370db ===================================== libraries/process ===================================== @@ -1 +1 @@ -Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e +Subproject commit f7d51387ba7f7f6079f3a9d5ce011ad9359b7dbb ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 6be36ed54cc035c0f095d24bf3a451638d45513c +Subproject commit 90e7d70de337ad759102b2445ebef6980684a9d3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3f91d63dadc6f063894504df393715... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3f91d63dadc6f063894504df393715... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Zubin (@wz1000)