[Git][ghc/ghc][master] Add missing entry to freeNamesItem (#18369)

Marge Bot gitlab at gitlab.haskell.org
Wed Jun 24 02:52:15 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00
Add missing entry to freeNamesItem (#18369)

- - - - -


3 changed files:

- compiler/GHC/Iface/Syntax.hs
- + testsuite/tests/driver/T18369.hs
- testsuite/tests/driver/all.T


Changes:

=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -1712,8 +1712,9 @@ freeNamesIfIdInfo :: IfaceIdInfo -> NameSet
 freeNamesIfIdInfo = fnList freeNamesItem
 
 freeNamesItem :: IfaceInfoItem -> NameSet
-freeNamesItem (HsUnfold _ u) = freeNamesIfUnfold u
-freeNamesItem _              = emptyNameSet
+freeNamesItem (HsUnfold _ u)         = freeNamesIfUnfold u
+freeNamesItem (HsLFInfo (IfLFCon n)) = unitNameSet n
+freeNamesItem _                      = emptyNameSet
 
 freeNamesIfUnfold :: IfaceUnfolding -> NameSet
 freeNamesIfUnfold (IfCoreUnfold _ e)     = freeNamesIfExpr e


=====================================
testsuite/tests/driver/T18369.hs
=====================================
@@ -0,0 +1,10 @@
+module T18369 where
+
+import Unsafe.Coerce
+import GHC.Exts (Any)
+
+{-# NOINLINE emptyRecord #-}
+emptyRecord :: Any
+emptyRecord = unsafeCoerce EmptyElement
+
+data TombStone = EmptyElement


=====================================
testsuite/tests/driver/all.T
=====================================
@@ -281,3 +281,4 @@ test('T16737',
 
 test('T17143', exit_code(1), run_command, ['{compiler} T17143.hs -S -fno-code'])
 test('T17786', unless(opsys('mingw32'), skip), makefile_test, [])
+test('T18369', normal, compile, ['-O'])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1f34d37b47826e86343e368a5c00f1a4b1f2bce
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/20200623/bec5363d/attachment-0001.html>


More information about the ghc-commits mailing list