[Git][ghc/ghc][wip/reinstallable-th] Restore implicit deps
Teo Camarasu (@teo)
gitlab at gitlab.haskell.org
Fri May 24 17:27:37 UTC 2024
Teo Camarasu pushed to branch wip/reinstallable-th at Glasgow Haskell Compiler / GHC
Commits:
ba9d2ad9 by Teo Camarasu at 2024-05-24T18:27:30+01:00
Restore implicit deps
- - - - -
4 changed files:
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Unit/State.hs
Changes:
=====================================
compiler/GHC/Iface/Recomp.hs
=====================================
@@ -596,7 +596,7 @@ checkDependencies hsc_env summary iface
liftIO $
check_mods (sort hs) prev_dep_mods
`recompThen`
- let allPkgDeps = sortBy (comparing snd) $ nubOrdOn snd ps
+ let allPkgDeps = sortBy (comparing snd) $ nubOrdOn snd (ps ++ implicit_deps)
in check_packages allPkgDeps prev_dep_pkgs
where
@@ -621,6 +621,8 @@ checkDependencies hsc_env summary iface
prev_dep_pkgs = Set.toAscList (Set.union (dep_direct_pkgs (mi_deps iface))
(dep_plugin_pkgs (mi_deps iface)))
+ implicit_deps = map (fsLit "Implicit",) (implicitPackageDeps dflags)
+
-- GHC.Prim is very special and doesn't appear in ms_textual_imps but
-- ghc-prim will appear in the package dependencies still. In order to not confuse
-- the recompilation logic we need to not forget we imported GHC.Prim.
=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -215,7 +215,11 @@ rnImports imports = do
let (decls, imp_user_spec, rdr_env, imp_avails, hpc_usage) = combine (stuff1 ++ stuff2)
-- Update imp_boot_mods if imp_direct_mods mentions any of them
let merged_import_avail = clobberSourceImports imp_avails
- return (decls, imp_user_spec, rdr_env, merged_import_avail, hpc_usage)
+ dflags <- getDynFlags
+ let final_import_avail =
+ merged_import_avail { imp_dep_direct_pkgs = S.fromList (implicitPackageDeps dflags)
+ `S.union` imp_dep_direct_pkgs merged_import_avail}
+ return (decls, imp_user_spec, rdr_env, final_import_avail, hpc_usage)
where
clobberSourceImports imp_avails =
=====================================
compiler/GHC/Runtime/Interpreter/JS.hs
=====================================
@@ -303,8 +303,8 @@ jsLinkObjects logger tmpfs tmp_dir cfg unit_env inst objs is_root = do
}
let units = preloadUnits (ue_units unit_env)
- ++ [ghcInternalUnitId] -- don't forget ghc-internal which is an implicit dep
- -- eg, for desugaring TH quotes
+ ++ [ghcInternalUnitId] -- don't forget ghc-internal which is an implicit dep
+ -- eg, for desugaring TH quotes
-- compute dependencies
let link_spec = LinkSpec
=====================================
compiler/GHC/Unit/State.hs
=====================================
@@ -68,7 +68,8 @@ module GHC.Unit.State (
pprWithUnitState,
-- * Utils
- unwireUnit)
+ unwireUnit,
+ implicitPackageDeps)
where
import GHC.Prelude
@@ -115,6 +116,7 @@ import Data.Set (Set)
import Data.Monoid (First(..))
import qualified Data.Semigroup as Semigroup
import qualified Data.Set as Set
+import GHC.LanguageExtensions
import Control.Applicative
-- ---------------------------------------------------------------------------
@@ -2266,3 +2268,11 @@ pprWithUnitState :: UnitState -> SDoc -> SDoc
pprWithUnitState state = updSDocContext (\ctx -> ctx
{ sdocUnitIdForUser = \fs -> pprUnitIdForUser state (UnitId fs)
})
+
+-- | Add package dependencies on the wired-in packages we use
+implicitPackageDeps :: DynFlags -> [UnitId]
+implicitPackageDeps dflags
+ = [ghcInternalUnitId | xopt TemplateHaskellQuotes dflags]
+ -- TODO: Should also include `base` and `ghc-prim` if we use those implicitly, but
+ -- it is possible to not depend on base (for example, see `ghc-prim`)
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba9d2ad947cdbb6c4ca94912cc61c3263819b2e9
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba9d2ad947cdbb6c4ca94912cc61c3263819b2e9
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/20240524/2f469a3f/attachment-0001.html>
More information about the ghc-commits
mailing list