Skip to content
Snippets Groups Projects
Commit cd7a1887 authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 2000-01-06 10:43:15 by simonmar]

Fix a bug in inlining that gave unresolved references
whenever you compile without -O.  Silly me.
parent e1016718
No related merge requests found
......@@ -19,7 +19,7 @@ module CoreUnfold (
noUnfolding, mkTopUnfolding, mkUnfolding, mkCompulsoryUnfolding, seqUnfolding,
mkOtherCon, otherCons,
unfoldingTemplate, maybeUnfoldingTemplate,
isEvaldUnfolding, isCheapUnfolding,
isEvaldUnfolding, isCheapUnfolding, isCompulsoryUnfolding,
hasUnfolding, hasSomeUnfolding,
couldBeSmallEnoughToInline,
......@@ -146,6 +146,10 @@ isCheapUnfolding :: Unfolding -> Bool
isCheapUnfolding (CoreUnfolding _ _ is_cheap _ _) = is_cheap
isCheapUnfolding other = False
isCompulsoryUnfolding :: Unfolding -> Bool
isCompulsoryUnfolding (CompulsoryUnfolding _) = True
isCompulsoryUnfolding other = False
hasUnfolding :: Unfolding -> Bool
hasUnfolding (CoreUnfolding _ _ _ _ _) = True
hasUnfolding (CompulsoryUnfolding _) = True
......
......@@ -51,10 +51,11 @@ module SimplMonad (
#include "HsVersions.h"
import Const ( Con(DEFAULT) )
import Id ( Id, mkSysLocal, isConstantId )
import Id ( Id, mkSysLocal, getIdUnfolding )
import IdInfo ( InlinePragInfo(..) )
import Demand ( Demand )
import CoreSyn
import CoreUnfold ( isCompulsoryUnfolding )
import PprCore () -- Instances
import Rules ( RuleBase )
import CostCentre ( CostCentreStack, subsumedCCS )
......@@ -744,7 +745,8 @@ environment seems like wild overkill.
\begin{code}
switchOffInlining :: SimplM a -> SimplM a
switchOffInlining m env us sc
= m (env { seBlackList = \v -> (v `isInScope` subst) || not (isLocallyDefined v)
= m (env { seBlackList = \v -> not (isCompulsoryUnfolding (getIdUnfolding v)) &&
((v `isInScope` subst) || not (isLocallyDefined v))
}) us sc
-- Black list anything that is in scope or imported.
-- The in-scope thing arranges *not* to black list inlinings that are
......@@ -758,6 +760,12 @@ switchOffInlining m env us sc
-- to inline them
-- But that failed because if we inline (say) [] in build's rhs, then
-- the exported thing doesn't match rules
--
-- But we must inline primops (which have compulsory unfoldings) in the
-- last phase of simplification, because they don't have bindings.
-- The simplifier now *never* inlines blacklisted things (even if they
-- have compulsory unfoldings) so we must not black-list compulsory
-- unfoldings inside INLINE prags.
where
subst = seSubst env
old_black_list = seBlackList env
......
......@@ -690,7 +690,6 @@ sub setupOptimiseFlags {
= (
'-fsimplify',
'[',
'-finline-phase2',
$Oopt_MaxSimplifierIterations,
']',
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment