[Git][ghc/ghc][wip/T23109] Don't make a closure table for type data decls

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Fri May 10 09:33:58 UTC 2024



Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC


Commits:
88db4251 by Simon Peyton Jones at 2024-05-10T10:33:29+01:00
Don't make a closure table for type data decls

- - - - -


1 changed file:

- compiler/GHC/StgToCmm.hs


Changes:

=====================================
compiler/GHC/StgToCmm.hs
=====================================
@@ -104,21 +104,12 @@ codeGen logger tmpfs cfg (InfoTableProvMap (UniqMap denv) _ _) tycons
         ; cg (mkModuleInit cost_centre_info (stgToCmmThisModule cfg) hpc_info)
 
         ; mapM_ (cg . cgTopBinding logger tmpfs cfg) stg_binds
-                -- Put datatype_stuff after code_stuff, because the
+                -- Put datatype_stuff (cgTyCon) after code_stuff (cgTopBinding), because the
                 -- datatype closure table (for enumeration types) to
                 -- (say) PrelBase_True_closure, which is defined in
                 -- code_stuff
-        ; let do_tycon tycon = do
-                -- Generate a table of static closures for an enumeration
-                -- type Note that the closure pointers are tagged.
-                 when (isEnumerationTyCon tycon) $
-                   cg (cgEnumerationTyCon tycon)
 
-                 -- Emit normal info_tables, for data constructors defined in this module.
-                 when (isDataTyCon tycon) $
-                   mapM_ (cg . cgDataCon DefinitionSite) (tyConDataCons tycon)
-
-        ; mapM_ do_tycon tycons
+        ; mapM_ (cg . cgTyCon) tycons
 
         -- Emit special info tables for everything used in this module
         -- This will only do something if  `-fdistinct-info-tables` is turned on.
@@ -222,11 +213,31 @@ mkModuleInit cost_centre_info this_mod hpc_info
 
 
 ---------------------------------------------------------------
---      Generating static stuff for algebraic data types
+--   Generating static stuff for algebraic data types, including
+--     * entry code for each data con
+--     * info table for each data con
+--     * for enumerations, a table of all the closures
+---------------------------------------------------------------
+
+---------------------------------------------------------------
+--      Data type constructors
 ---------------------------------------------------------------
+cgTyCon :: TyCon -> FCode ()
+-- Generate static data for each algebraic data type
+cgTyCon tycon
+  | not (isDataTyCon tycon)  -- Type families, newtypes, and `type data` constructors
+  = return ()
+
+  | otherwise   -- An honest-to-goodness algebraic data type
+  = do { -- Emit normal info_tables, for data constructors defined in this module.
+         mapM_ (cgDataCon DefinitionSite) (tyConDataCons tycon)
 
+       ; when (isEnumerationTyCon tycon) $
+         cgEnumerationTyCon tycon }
 
 cgEnumerationTyCon :: TyCon -> FCode ()
+-- Generate a table of static closures for an enumeration type.
+-- Note that the closure pointers in the table are tagged.
 cgEnumerationTyCon tycon
   = do platform <- getPlatform
        emitRODataLits (mkClosureTableLabel (tyConName tycon) NoCafRefs)
@@ -234,7 +245,6 @@ cgEnumerationTyCon tycon
                            (tagForCon platform con)
              | con <- tyConDataCons tycon]
 
-
 cgDataCon :: ConInfoTableLocation -> DataCon -> FCode ()
 -- Generate the entry code, info tables, and (for niladic constructor)
 -- the static closure, for a constructor.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/88db425117087c0e7b63d343628bd008b5b1ca8c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/88db425117087c0e7b63d343628bd008b5b1ca8c
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/20240510/8c494feb/attachment-0001.html>


More information about the ghc-commits mailing list