[Git][ghc/ghc][wip/T23942] Even more implicit dependency import stuff
Matthew Craven (@clyring)
gitlab at gitlab.haskell.org
Sat Mar 9 12:47:43 UTC 2024
Matthew Craven pushed to branch wip/T23942 at Glasgow Haskell Compiler / GHC
Commits:
62c6ce49 by Matthew Craven at 2024-03-09T07:46:58-05:00
Even more implicit dependency import stuff
- - - - -
3 changed files:
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Conc/Internal.hs
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/Base.hs
=====================================
@@ -370,7 +370,7 @@ imports of X must include Y.
Such implicit dependencies can be introduced in at least the following ways:
W1:
- Awkward dependencies:
+ Common awkward dependencies:
* TypeRep metadata introduces references to GHC.Types in EVERY module.
* A String literal introduces a reference to GHC.CString, for either
unpackCString# or unpackCStringUtf8# depending on its contents.
@@ -443,6 +443,11 @@ W5:
type-checking. (This doesn't apply to hs-boot files, which can't
be given "default" declarations anyway.)
+W6:
+ In the wasm backend, JSFFI imports and exports pull in a bunch of stuff;
+ see Note [Desugaring JSFFI static export] and Note [Desugaring JSFFI import]
+ in GHC.HsToCore.Foreign.Wasm.
+
A complete list could probably be made by going through the known-key
names in GHC.Builtin.Names and GHC.Builtin.Names.TH. To test whether
the transitive imports are sufficient for any single module, instruct
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot
=====================================
@@ -2,5 +2,8 @@
module GHC.Internal.Exception.Context where
+-- See W1 of Note [Tracking dependencies on primitives] in GHC.Internal.Base
+import GHC.Types ()
+
data ExceptionContext
=====================================
libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Conc/Internal.hs
=====================================
@@ -7,6 +7,9 @@ module GHC.Internal.Wasm.Prim.Conc.Internal (
import GHC.Internal.Base
import GHC.Internal.IO
+-- See W6 of Note [Tracking dependencies on primitives] in GHC.Internal.Base
+import GHC.Internal.Wasm.Prim.Imports ()
+
foreign import javascript safe "new Promise(res => setTimeout(res, $1 / 1000))"
js_delay :: Int -> IO ()
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/62c6ce498cd2bd1fe0cf8e17cfc7d84fa3ae44c0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/62c6ce498cd2bd1fe0cf8e17cfc7d84fa3ae44c0
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/20240309/42437382/attachment-0001.html>
More information about the ghc-commits
mailing list