never executed always true always false
1
2
3 module GHC.Stg.Subst where
4
5 import GHC.Prelude
6
7 import GHC.Types.Id
8 import GHC.Types.Var.Env
9 import GHC.Utils.Monad.State.Strict
10
11 import GHC.Utils.Outputable
12 import GHC.Utils.Misc
13 import GHC.Utils.Panic
14 import GHC.Utils.Trace
15
16 -- | A renaming substitution from 'Id's to 'Id's. Like 'RnEnv2', but not
17 -- maintaining pairs of substitutions. Like 'GHC.Core.Subst.Subst', but
18 -- with the domain being 'Id's instead of entire 'CoreExpr'.
19 data Subst = Subst InScopeSet IdSubstEnv
20
21 type IdSubstEnv = IdEnv Id
22
23 -- | @emptySubst = 'mkEmptySubst' 'emptyInScopeSet'@
24 emptySubst :: Subst
25 emptySubst = mkEmptySubst emptyInScopeSet
26
27 -- | Constructs a new 'Subst' assuming the variables in the given 'InScopeSet'
28 -- are in scope.
29 mkEmptySubst :: InScopeSet -> Subst
30 mkEmptySubst in_scope = Subst in_scope emptyVarEnv
31
32 -- | Substitutes an 'Id' for another one according to the 'Subst' given in a way
33 -- that avoids shadowing the 'InScopeSet', returning the result and an updated
34 -- 'Subst' that should be used by subsequent substitutions.
35 substBndr :: Id -> Subst -> (Id, Subst)
36 substBndr id (Subst in_scope env)
37 = (new_id, Subst new_in_scope new_env)
38 where
39 new_id = uniqAway in_scope id
40 no_change = new_id == id -- in case nothing shadowed
41 new_in_scope = in_scope `extendInScopeSet` new_id
42 new_env
43 | no_change = delVarEnv env id
44 | otherwise = extendVarEnv env id new_id
45
46 -- | @substBndrs = runState . traverse (state . substBndr)@
47 substBndrs :: Traversable f => f Id -> Subst -> (f Id, Subst)
48 substBndrs = runState . traverse (state . substBndr)
49
50 -- | Substitutes an occurrence of an identifier for its counterpart recorded
51 -- in the 'Subst'.
52 lookupIdSubst :: HasCallStack => Id -> Subst -> Id
53 lookupIdSubst id (Subst in_scope env)
54 | not (isLocalId id) = id
55 | Just id' <- lookupVarEnv env id = id'
56 | Just id' <- lookupInScope in_scope id = id'
57 | otherwise = warnPprTrace True (text "StgSubst.lookupIdSubst" <+> ppr id $$ ppr in_scope) id
58
59 -- | Substitutes an occurrence of an identifier for its counterpart recorded
60 -- in the 'Subst'. Does not generate a debug warning if the identifier to
61 -- to substitute wasn't in scope.
62 noWarnLookupIdSubst :: HasCallStack => Id -> Subst -> Id
63 noWarnLookupIdSubst id (Subst in_scope env)
64 | not (isLocalId id) = id
65 | Just id' <- lookupVarEnv env id = id'
66 | Just id' <- lookupInScope in_scope id = id'
67 | otherwise = id
68
69 -- | Add the 'Id' to the in-scope set and remove any existing substitutions for
70 -- it.
71 extendInScope :: Id -> Subst -> Subst
72 extendInScope id (Subst in_scope env) = Subst (in_scope `extendInScopeSet` id) env
73
74 -- | Add a substitution for an 'Id' to the 'Subst': you must ensure that the
75 -- in-scope set is such that TyCoSubst Note [The substitution invariant]
76 -- holds after extending the substitution like this.
77 extendSubst :: Id -> Id -> Subst -> Subst
78 extendSubst id new_id (Subst in_scope env)
79 = assertPpr (new_id `elemInScopeSet` in_scope) (ppr id <+> ppr new_id $$ ppr in_scope) $
80 Subst in_scope (extendVarEnv env id new_id)