[Git][ghc/ghc][wip/modiface-nfdata-format] compiler: Use NamedFieldPuns for `ModIface_` and `ModIfaceBackend` `NFData`

Zubin (@wz1000) gitlab at gitlab.haskell.org
Thu Feb 9 14:17:53 UTC 2023



Zubin pushed to branch wip/modiface-nfdata-format at Glasgow Haskell Compiler / GHC


Commits:
4fc35400 by Zubin Duggal at 2023-02-09T19:47:41+05:30
compiler: Use NamedFieldPuns for `ModIface_` and `ModIfaceBackend` `NFData`
instances

This is a minor refactor that makes it easy to add and remove fields from
`ModIface_` and `ModIfaceBackend`.

Also change the formatting to make it clear exactly which fields are
fully forced with `rnf`

- - - - -


1 changed file:

- compiler/GHC/Unit/Module/ModIface.hs


Changes:

=====================================
compiler/GHC/Unit/Module/ModIface.hs
=====================================
@@ -3,6 +3,7 @@
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Unit.Module.ModIface
    ( ModIface
@@ -549,20 +550,58 @@ emptyIfaceHashCache _occ = Nothing
 
 -- Take care, this instance only forces to the degree necessary to
 -- avoid major space leaks.
-instance (NFData (IfaceBackendExts (phase :: ModIfacePhase)), NFData (IfaceDeclExts (phase :: ModIfacePhase))) => NFData (ModIface_ phase) where
-  rnf (ModIface f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12
-                f13 f14 f15 f16 f17 f18 f19 f20 f21 f22 f23 f24) =
-    rnf f1 `seq` rnf f2 `seq` f3 `seq` f4 `seq` f5 `seq` f6 `seq` rnf f7 `seq` f8 `seq`
-    f9 `seq` rnf f10 `seq` rnf f11 `seq` rnf f12 `seq` f13 `seq` rnf f14 `seq` rnf f15 `seq` rnf f16 `seq`
-    rnf f17 `seq` f18 `seq` rnf f19 `seq` rnf f20 `seq` rnf f21 `seq` f22 `seq` f23 `seq` rnf f24
+instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase))
+         , NFData (IfaceDeclExts (phase :: ModIfacePhase))
+         ) => NFData (ModIface_ phase) where
+  rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages
+               , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns
+               , mi_decls, mi_extra_decls, mi_globals, mi_insts
+               , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg
+               , mi_complete_matches, mi_docs, mi_final_exts
+               , mi_ext_fields, mi_src_hash})
+    =     rnf mi_module
+    `seq` rnf mi_sig_of
+    `seq`     mi_hsc_src
+    `seq`     mi_deps
+    `seq`     mi_usages
+    `seq`     mi_exports
+    `seq` rnf mi_used_th
+    `seq`     mi_fixities
+    `seq`     mi_warns
+    `seq` rnf mi_anns
+    `seq` rnf mi_decls
+    `seq` rnf mi_extra_decls
+    `seq`     mi_globals
+    `seq` rnf mi_insts
+    `seq` rnf mi_fam_insts
+    `seq` rnf mi_rules
+    `seq` rnf mi_hpc
+    `seq`     mi_trust
+    `seq` rnf mi_trust_pkg
+    `seq` rnf mi_complete_matches
+    `seq` rnf mi_docs
+    `seq`     mi_final_exts
+    `seq`     mi_ext_fields
+    `seq` rnf mi_src_hash
     `seq` ()
 
-
 instance NFData (ModIfaceBackend) where
-  rnf (ModIfaceBackend f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12 f13)
-    = rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq`
-      rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq`
-      rnf f9 `seq` rnf f10 `seq` rnf f11 `seq` rnf f12 `seq` rnf f13
+  rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash
+                      , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash
+                      , mi_orphan_hash, mi_warn_fn, mi_fix_fn, mi_hash_fn})
+    =     rnf mi_iface_hash
+    `seq` rnf mi_mod_hash
+    `seq` rnf mi_flag_hash
+    `seq` rnf mi_opt_hash
+    `seq` rnf mi_hpc_hash
+    `seq` rnf mi_plugin_hash
+    `seq` rnf mi_orphan
+    `seq` rnf mi_finsts
+    `seq` rnf mi_exp_hash
+    `seq` rnf mi_orphan_hash
+    `seq` rnf mi_warn_fn
+    `seq` rnf mi_fix_fn
+    `seq` rnf mi_hash_fn
 
 
 forceModIface :: ModIface -> IO ()



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4fc354006c55ac5ef609ab6a5ef2201836eac96a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4fc354006c55ac5ef609ab6a5ef2201836eac96a
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/20230209/d048a128/attachment-0001.html>


More information about the ghc-commits mailing list