Skip to content
Draft
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
20 changes: 14 additions & 6 deletions compiler/GHC/StgToJS/Linker/Linker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE MultiWayIf #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -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: " <> (showPprUnsafe u))
| otherwise
-> pure foundArchives
where
ue_state = ue_homeUnitState unit_env

Expand Down