Skip to content
Snippets Groups Projects
Commit 3bbd2bf2 authored by Ben Gamari's avatar Ben Gamari
Browse files

compiler/tc: Small optimisation of evCallStack

Don't lookupIds unless we actually need them.
parent 317a915b
No related branches found
No related tags found
No related merge requests found
......@@ -38,7 +38,9 @@ evDelayedError ty msg
evCallStack :: (MonadThings m, HasModule m, HasDynFlags m) =>
EvCallStack -> m EvExpr
-- See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
evCallStack cs = do
evCallStack EvCsEmpty =
Var <$> lookupId emptyCallStackName
evCallStack (EvCsPushCall fs loc tm) = do
df <- getDynFlags
let platform = targetPlatform df
m <- getModule
......@@ -53,8 +55,6 @@ evCallStack cs = do
, return $ mkIntExprInt platform (srcSpanEndCol l)
]
emptyCS <- Var <$> lookupId emptyCallStackName
pushCSVar <- lookupId pushCallStackName
let pushCS name loc rest =
mkCoreApps (Var pushCSVar) [mkCoreTup [name, loc], rest]
......@@ -69,6 +69,4 @@ evCallStack cs = do
let ip_co = unwrapIP (exprType tm)
return (pushCS nameExpr locExpr (Cast tm ip_co))
case cs of
EvCsPushCall fs loc tm -> mkPush fs loc tm
EvCsEmpty -> return emptyCS
mkPush fs loc tm
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