Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 91b6be10 by Julian Ospald at 2025-10-20T18:21:03-04:00 Improve error handling in 'getPackageArchives' When the library dirs in the package conf files are not set up correctly, the JS linker will happily ignore such packages and not link against them, although they're part of the link plan. Fixes #26383 - - - - - 1 changed file: - compiler/GHC/StgToJS/Linker/Linker.hs Changes: ===================================== compiler/GHC/StgToJS/Linker/Linker.hs ===================================== @@ -2,6 +2,7 @@ {-# LANGUAGE TupleSections #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE BlockArguments #-} +{-# LANGUAGE MultiWayIf #-} ----------------------------------------------------------------------------- -- | @@ -666,12 +667,19 @@ renderLinkerStats s = getPackageArchives :: StgToJSConfig -> UnitEnv -> [UnitId] -> IO [FilePath] -getPackageArchives cfg unit_env units = - filterM doesFileExist [ ST.unpack p > "lib" ++ ST.unpack l ++ profSuff <.> "a" - | u <- units - , p <- getInstalledPackageLibDirs ue_state u - , l <- getInstalledPackageHsLibs ue_state u - ] +getPackageArchives cfg unit_env units = do + fmap concat $ forM units $ \u -> do + let archives = [ ST.unpack p > "lib" ++ ST.unpack l ++ profSuff <.> "a" + | p <- getInstalledPackageLibDirs ue_state u + , l <- getInstalledPackageHsLibs ue_state u + ] + foundArchives <- filterM doesFileExist archives + if | not (null archives) + , null foundArchives + -> do + throwGhcExceptionIO (InstallationError $ "Could not find any library archives for unit-id: " <> (renderWithContext (csContext cfg) $ ppr u)) + | otherwise + -> pure foundArchives where ue_state = ue_homeUnitState unit_env View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91b6be10bd58c2bfc1c7c22e81b06ab3... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91b6be10bd58c2bfc1c7c22e81b06ab3... You're receiving this email because of your account on gitlab.haskell.org.