[Git][ghc/ghc][wip/cleanup-selfboot] cleanup: Remove unused field from SelfBoot

Krzysztof Gogolewski (@monoidal) gitlab at gitlab.haskell.org
Tue May 30 19:18:16 UTC 2023



Krzysztof Gogolewski pushed to branch wip/cleanup-selfboot at Glasgow Haskell Compiler / GHC


Commits:
112c2201 by Krzysztof Gogolewski at 2023-05-30T21:16:49+02:00
cleanup: Remove unused field from SelfBoot

It is no longer needed since Note [Extra dependencies from .hs-boot files]
was deleted in 6998772043.

I've also added tildes to Note headers, otherwise they're not detected
by the linter.

- - - - -


8 changed files:

- compiler/GHC/IfaceToCore.hs
- compiler/GHC/JS/Optimizer.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/Types.hs
- testsuite/driver/testlib.py
- testsuite/mk/boilerplate.mk
- testsuite/tests/linters/notes.stdout


Changes:

=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -114,7 +114,6 @@ import GHC.Types.Var as Var
 import GHC.Types.Var.Set
 import GHC.Types.Name
 import GHC.Types.Name.Env
-import GHC.Types.Name.Set
 import GHC.Types.Id
 import GHC.Types.Id.Make
 import GHC.Types.Id.Info
@@ -568,7 +567,7 @@ tcHiBootIface hsc_src mod
           then do { (_, hug) <- getEpsAndHug
                  ; case lookupHugByModule mod hug  of
                       Just info | mi_boot (hm_iface info) == IsBoot
-                                -> mkSelfBootInfo (hm_iface info) (hm_details info)
+                                -> mkSelfBootInfo (hm_details info)
                       _ -> return NoSelfBoot }
           else do
 
@@ -584,7 +583,7 @@ tcHiBootIface hsc_src mod
         ; case read_result of {
             Succeeded (iface, _path) ->
               do { tc_iface <- initIfaceTcRn $ typecheckIface iface
-                 ; mkSelfBootInfo iface tc_iface } ;
+                 ; mkSelfBootInfo tc_iface } ;
             Failed err               ->
 
         -- There was no hi-boot file. But if there is circularity in
@@ -613,28 +612,8 @@ tcHiBootIface hsc_src mod
     need = text "Need the hi-boot interface for" <+> ppr mod
                  <+> text "to compare against the Real Thing"
 
-mkSelfBootInfo :: ModIface -> ModDetails -> TcRn SelfBootInfo
-mkSelfBootInfo iface mds
-  = do -- NB: This is computed DIRECTLY from the ModIface rather
-       -- than from the ModDetails, so that we can query 'sb_tcs'
-       -- WITHOUT forcing the contents of the interface.
-       let tcs = map ifName
-                 . filter isIfaceTyCon
-                 . map snd
-                 $ mi_decls iface
-       return $ SelfBoot { sb_mds = mds
-                         , sb_tcs = mkNameSet tcs }
-  where
-    -- Returns @True@ if, when you call 'tcIfaceDecl' on
-    -- this 'IfaceDecl', an ATyCon would be returned.
-    -- NB: This code assumes that a TyCon cannot be implicit.
-    isIfaceTyCon IfaceId{}      = False
-    isIfaceTyCon IfaceData{}    = True
-    isIfaceTyCon IfaceSynonym{} = True
-    isIfaceTyCon IfaceFamily{}  = True
-    isIfaceTyCon IfaceClass{}   = True
-    isIfaceTyCon IfaceAxiom{}   = False
-    isIfaceTyCon IfacePatSyn{}  = False
+mkSelfBootInfo :: ModDetails -> TcRn SelfBootInfo
+mkSelfBootInfo mds = return $ SelfBoot { sb_mds = mds }
 
 {-
 ************************************************************************


=====================================
compiler/GHC/JS/Optimizer.hs
=====================================
@@ -47,9 +47,8 @@ import GHC.JS.Syntax
 import Control.Arrow
 
 {-
-Note [ Unsafe JavaScript Optimizations ]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
+Note [Unsafe JavaScript optimizations]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 There are a number of optimizations that the JavaScript Backend performs that
 are not sound with respect to arbritrary JavaScript. We still perform these
 optimizations because we are not optimizing arbritrary javascript and under the


=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -698,9 +698,6 @@ tcRnHsBootDecls boot_or_sig decls
                             , hs_valds  = XValBindsLR (NValBinds val_binds val_sigs) })
               <- rnTopSrcDecls first_group
 
-        -- The empty list is for extra dependencies coming from .hs-boot files
-        -- See Note [Extra dependencies from .hs-boot files] in GHC.Rename.Module
-
         ; (gbl_env, lie) <- setGblEnv tcg_env $ captureTopConstraints $ do {
               -- NB: setGblEnv **before** captureTopConstraints so that
               -- if the latter reports errors, it knows what's in scope


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -5006,7 +5006,7 @@ checkValidRoleAnnots role_annots tc
       = whenIsJust role_annot_decl_maybe illegalRoleAnnotDecl
 
 -- Note [Missing role annotations warning]
---
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 -- We warn about missing role annotations for tycons
 -- 1. not type-classes:
 --    type classes are nominal by default, which is most conservative


=====================================
compiler/GHC/Tc/Types.hs
=====================================
@@ -687,10 +687,7 @@ instance ContainsModule TcGblEnv where
 data SelfBootInfo
   = NoSelfBoot    -- No corresponding hi-boot file
   | SelfBoot
-       { sb_mds :: ModDetails   -- There was a hi-boot file,
-       , sb_tcs :: NameSet }    -- defining these TyCons,
--- What is sb_tcs used for?  See Note [Extra dependencies from .hs-boot files]
--- in GHC.Rename.Module
+       { sb_mds :: ModDetails }  -- There was a hi-boot file
 
 bootExports :: SelfBootInfo -> NameSet
 bootExports boot =


=====================================
testsuite/driver/testlib.py
=====================================
@@ -167,7 +167,7 @@ def stage1(name, opts):
                    'add your test to testsuite/tests/stage1 instead')
 
 # Note [Why is there no stage1 setup function?]
-#
+# ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 # Presumably a stage1 setup function would signal that the stage1
 # compiler should be used to compile a test.
 #


=====================================
testsuite/mk/boilerplate.mk
=====================================
@@ -265,7 +265,7 @@ ifeq "$(findstring clean,$(MAKECMDGOALS))" ""
 endif
 
 # Note [WayFlags]
-#
+# ~~~~~~~~~~~~~~~
 # Code that uses TemplateHaskell should either use -fexternal-interpreter, or
 # be built in the same way as the compiler (-prof, -dynamic or -static).
 #


=====================================
testsuite/tests/linters/notes.stdout
=====================================
@@ -15,7 +15,6 @@ ref    compiler/GHC/Hs/Extension.hs:146:5:     Note [Strict argument type constr
 ref    compiler/GHC/Hs/Pat.hs:143:74:     Note [Lifecycle of a splice]
 ref    compiler/GHC/HsToCore/Pmc/Solver.hs:858:20:     Note [COMPLETE sets on data families]
 ref    compiler/GHC/HsToCore/Quote.hs:1476:7:     Note [How brackets and nested splices are handled]
-ref    compiler/GHC/JS/Optimizer.hs:259:47:     Note [Unsafe JavaScript optimizations]
 ref    compiler/GHC/Stg/Unarise.hs:442:32:     Note [Renaming during unarisation]
 ref    compiler/GHC/StgToCmm.hs:106:18:     Note [codegen-split-init]
 ref    compiler/GHC/StgToCmm.hs:109:18:     Note [pipeline-split-init]
@@ -31,12 +30,8 @@ ref    compiler/GHC/Tc/Gen/Splice.hs:531:35:     Note [PendingRnSplice]
 ref    compiler/GHC/Tc/Gen/Splice.hs:655:7:     Note [How brackets and nested splices are handled]
 ref    compiler/GHC/Tc/Gen/Splice.hs:888:11:     Note [How brackets and nested splices are handled]
 ref    compiler/GHC/Tc/Instance/Family.hs:474:35:     Note [Constrained family instances]
-ref    compiler/GHC/Tc/Module.hs:711:15:     Note [Extra dependencies from .hs-boot files]
 ref    compiler/GHC/Tc/Solver/Rewrite.hs:1009:7:     Note [Stability of rewriting]
 ref    compiler/GHC/Tc/TyCl.hs:1130:6:     Note [Unification variables need fresh Names]
-ref    compiler/GHC/Tc/TyCl.hs:4982:17:     Note [Missing role annotations warning]
-ref    compiler/GHC/Tc/TyCl.hs:5008:3:     Note [Missing role annotations warning]
-ref    compiler/GHC/Tc/Types.hs:692:33:     Note [Extra dependencies from .hs-boot files]
 ref    compiler/GHC/Tc/Types/Constraint.hs:226:34:     Note [NonCanonical Semantics]
 ref    compiler/GHC/Types/Demand.hs:302:25:     Note [Preserving Boxity of results is rarely a win]
 ref    compiler/GHC/Unit/Module/Deps.hs:81:13:     Note [Structure of dep_boot_mods]
@@ -47,10 +42,6 @@ ref    docs/core-spec/core-spec.mng:177:6:     Note [TyBinders]
 ref    hadrian/src/Expression.hs:145:30:     Note [Linking ghc-bin against threaded stage0 RTS]
 ref    linters/lint-notes/Notes.hs:32:29:     Note [" <> T.unpack x <> "]
 ref    linters/lint-notes/Notes.hs:69:22:     Note [...]
-ref    testsuite/config/ghc:276:10:     Note [WayFlags]
-ref    testsuite/driver/testlib.py:165:10:     Note [Why is there no stage1 setup function?]
-ref    testsuite/driver/testlib.py:169:2:     Note [Why is there no stage1 setup function?]
-ref    testsuite/mk/boilerplate.mk:267:2:     Note [WayFlags]
 ref    testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs:30:27:     Note [Extra TcS Untouchables]
 ref    testsuite/tests/perf/should_run/all.T:8:6:     Note [Solving from instances when interacting Dicts]
 ref    testsuite/tests/polykinds/CuskFam.hs:16:11:     Note [Unifying implicit CUSK variables]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/112c2201e01208f237f26c4d0b10c755f5444b76

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/112c2201e01208f237f26c4d0b10c755f5444b76
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/20230530/11b0815b/attachment-0001.html>


More information about the ghc-commits mailing list