[Git][ghc/ghc][wip/T23942] Keep explicit imports for built-in deps in ghc-prim
Matthew Craven (@clyring)
gitlab at gitlab.haskell.org
Wed Mar 6 00:51:00 UTC 2024
Matthew Craven pushed to branch wip/T23942 at Glasgow Haskell Compiler / GHC
Commits:
7ed41803 by Matthew Craven at 2024-03-05T19:49:06-05:00
Keep explicit imports for built-in deps in ghc-prim
It's very sad to have to do so, but see wrinkle TID3.
Hopefully this changes soon.
- - - - -
2 changed files:
- compiler/GHC/Driver/MakeFile.hs
- libraries/ghc-prim/GHC/Tuple.hs
Changes:
=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -306,7 +306,7 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ node))
mhome_unit = hsc_home_unit_maybe hsc_env
mb_found <- findExactModule fc fopts other_fopts unit_state mhome_unit im
case mb_found of
- InstalledFound ml _ -> handle_hi_file (ml_hi_file ml)
+ InstalledFound modLoc _ -> handle_hi_file (ml_hi_file modLoc)
InstalledNoPackage _ -> panic "processDeps.do_implicit_import"
InstalledNotFound _ _ -> panic "processDeps.do_implicit_import"
@@ -314,12 +314,16 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ node))
; unless (ms_mod node == gHC_TYPES) $
do_implicit_import gHC_TYPES
- -- A module may implicitly depend on GHC.Tuple if ListTuplePuns is set
; unless (isHomeUnitInstanceOf (hsc_home_unit hsc_env) primUnitId) $ do
- { -- see Note [Tracking implicit dependencies], wrinkle TID2
- when (xopt ListTuplePuns dflags) $
- do_implicit_import gHC_INTERNAL_TUPLE
- -- see Note [Tracking implicit dependencies], wrinkle TID4
+ { -- A module may implicitly depend on GHC.Tuple and GHC.Classes
+ -- if ListTuplePuns is set, but see wrinkle TID2.
+ when (xopt ListTuplePuns dflags) $ do
+ { do_implicit_import gHC_INTERNAL_TUPLE
+ ; do_implicit_import gHC_CLASSES
+ }
+
+ -- Any module containing a string literal implicitly
+ -- depends on GHC.CString, but see wrinkle TID4.
; do_implicit_import gHC_CSTRING
}
}
@@ -332,6 +336,7 @@ files to look up even if they are not imported. They include
* Monad-related stuff in GHC.Internal.Base, if `do` notation is used
* Tuple-related stuff in GHC.Tuple, if the built-in tuple syntax is used
+ * Constraint tuples in GHC.Classes, if the built-in tuple syntax is used
* TypeRep-related stuff in GHC.Types, unless `-dno-typeable-binds` is set
* deriving-related stuff mostly elsewhere in ghc-prim
* GHC.CString.unpackCString# et al, if string literals are used
@@ -342,13 +347,13 @@ interfaces. So we include them in our -M output if -include-pkg-deps
is set, with the following wrinkles:
(TID1) We don't actually bother adding implicit dependencies for
- Monad, Arrow, etc. because the program will presumably fail to
- typecheck unless these are reachable via explicit imports anyway.
+ Monad, Arrow, etc. because the program will fail to typecheck anyway
+ unless these are reachable via explicit imports.
-(TID2) Users can opt out of implicitly depending on GHC.Tuple with the
- NoListTuplePuns languge extension. Ideally we would just turn off
- ListTuplePuns in the bits of ghc-prim that GHC.Tuple depends on, but
- when I tried, I got stupid errors like this:
+(TID2) Users can opt out of implicitly depending on GHC.Tuple and
+ GHC.Classes with the NoListTuplePuns languge extension. Ideally we
+ would just turn off ListTuplePuns in the bits of ghc-prim that these
+ modules depend on, but when I tried, I got stupid errors like this:
libraries/ghc-prim/GHC/Types.hs:371:15: error: [GHC-46574]
Cannot parse data constructor in a data/newtype declaration: []
@@ -358,22 +363,41 @@ is set, with the following wrinkles:
So for now we don't emit this dependency in the `ghc-prim` package,
which must explicitly import GHC.Tuple for build-order reasons.
- Yuck! But this doesn't make things in `ghc-prim` much worse, because
-
-(TID3) We don't even try to track dependencies involving `deriving`.
- We try to prevent this from causing problems by ensuring that any
- machinery `deriving` needs to reference related to a typeclass is
- imported from the defining module for that class. For example, the
- class Eq is defined in GHC.Classes, and derived Eq instances can
- reference GHC.Magic.dataToTag#. So we make sure that GHC.Magic is
- imported in GHC.Classes.
+ Yuck! But this doesn't make things in `ghc-prim` much worse, because...
+
+(TID3) Although we emit these extra dependencies with -M, this happens
+ via special handling in this file and GHC's downsweep does not
+ report these dependencies properly. Doing so would require a
+ breaking change to ModSummary to create a place to store these
+ built-in implicit dependencies in the output of downsweep, and is
+ left as future work.
+
+ But for now this causes problems with documentation generation for
+ ghc-prim unless its internal dependencies are indicated by actual
+ import statements. Since ghc-prim is fairly small and generally
+ plays by its own rules anyway, this situation is deemed acceptable
+ for now.
+
+(TID4) Since we don't have a flag to disable string literals, any
+ module could potentially contain one and thus reference GHC.CString.
+ To avoid cyclic dependency problems, we don't emit this potential
+ implicit dependency on GHC.CString for any modules in `ghc-prim`.
+
+ If there were any string literals in ghc-prim, their containing
+ modules would need to explicitly import GHC.CString. (But as of
+ March 2024 there are none anyway.)
+
+(TID5) We only indirectly track dependencies introduced by `deriving`.
+ Instead, we ensure that any machinery that might be referenced in a
+ derived instance for a class is imported in the module that defines
+ that class. For example, the class Eq is defined in GHC.Classes,
+ and derived Eq instances can reference GHC.Magic.dataToTag#. So we
+ make sure that GHC.Magic is imported in GHC.Classes. Then, since
+ any module containing a derived Eq instance must import Eq, such a
+ module automatically transitively depends on GHC.Magic.
Failing to do this for the Lift class caused #22229, which is sadly
still open as of March 2024.
-
-(TID4) Likewise, since we don't have a flag to disable string
- literals, we always add an implicit dependency on GHC.CString for
- any modules outside of `ghc-prim`.
-}
findDependency :: HscEnv
=====================================
libraries/ghc-prim/GHC/Tuple.hs
=====================================
@@ -29,6 +29,8 @@ module GHC.Tuple (
Tuple60(..), Tuple61(..), Tuple62(..), Tuple63(..), Tuple64(..),
) where
+import GHC.Types () -- This import is for build ordering. (wrinkle TID3)
+
default () -- Double and Integer aren't available yet
-- | The unit datatype @Unit@ has one non-undefined member, the nullary
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7ed418039b26d7cc6ca442e41273caf589523c8a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7ed418039b26d7cc6ca442e41273caf589523c8a
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/20240305/74c5997b/attachment-0001.html>
More information about the ghc-commits
mailing list