[GHC] #9279: Local wrapper function remains in final program; result = extra closure allocation
GHC
ghc-devs at haskell.org
Mon Sep 10 11:54:18 UTC 2018
#9279: Local wrapper function remains in final program; result = extra closure
allocation
-------------------------------------+-------------------------------------
Reporter: simonmar | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords: LateLamLift
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by sgraf):
Here's a diff that handles all `UnliftedRep`s uniformly:
{{{
diff --git a/compiler/basicTypes/Literal.hs
b/compiler/basicTypes/Literal.hs
index 21f4a92290..0e9f25f51e 100644
--- a/compiler/basicTypes/Literal.hs
+++ b/compiler/basicTypes/Literal.hs
@@ -62,6 +62,7 @@ import Binary
import Constants
import DynFlags
import Platform
+import RepType
import UniqFM
import Util
@@ -614,11 +615,14 @@ literalType (LitNumber _ _ t) = t
absentLiteralOf :: TyCon -> Maybe Literal
-- Return a literal of the appropriate primitive
-- TyCon, to use as a placeholder when it doesn't matter
-absentLiteralOf tc = lookupUFM absent_lits (tyConName tc)
+absentLiteralOf tc
+ | tyConPrimRep tc == [UnliftedRep]
+ = ASSERT (isUnliftedTyCon tc) Just MachNullAddr
+ | otherwise
+ = lookupUFM absent_lits (tyConName tc)
absent_lits :: UniqFM Literal
-absent_lits = listToUFM [ (addrPrimTyConKey, MachNullAddr)
- , (charPrimTyConKey, MachChar 'x')
+absent_lits = listToUFM [ (charPrimTyConKey, MachChar 'x')
, (intPrimTyConKey, mkMachIntUnchecked 0)
, (int64PrimTyConKey, mkMachInt64Unchecked 0)
, (wordPrimTyConKey, mkMachWordUnchecked 0)
}}}
But now `MachNullAddr` isn't always a literal of type `Addr#`. In
particular, the definition
{{{
-- | Find the Haskell 'Type' the literal occupies
literalType :: Literal -> Type
literalType MachNullAddr = addrPrimTy
literalType (MachChar _) = charPrimTy
literalType (MachStr _) = addrPrimTy
}}}
is probably a lie. But then it also lies for `MachStr` and `MachLabel`s,
so maybe this isn't such a bad thing? The binding should be immediately
eliminated by the simplifier, after all.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9279#comment:15>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list