module GHC.Stg.Subst where
import GHC.Prelude
import GHC.Types.Id
import GHC.Types.Var.Env
import GHC.Utils.Monad.State.Strict
import GHC.Utils.Outputable
import GHC.Utils.Misc
import GHC.Utils.Panic
data Subst = Subst InScopeSet IdSubstEnv
type IdSubstEnv = IdEnv Id
emptySubst :: Subst
emptySubst :: Subst
emptySubst = InScopeSet -> Subst
mkEmptySubst InScopeSet
emptyInScopeSet
mkEmptySubst :: InScopeSet -> Subst
mkEmptySubst :: InScopeSet -> Subst
mkEmptySubst InScopeSet
in_scope = InScopeSet -> IdSubstEnv -> Subst
Subst InScopeSet
in_scope IdSubstEnv
forall a. VarEnv a
emptyVarEnv
substBndr :: Id -> Subst -> (Id, Subst)
substBndr :: Id -> Subst -> (Id, Subst)
substBndr Id
id (Subst InScopeSet
in_scope IdSubstEnv
env)
= (Id
new_id, InScopeSet -> IdSubstEnv -> Subst
Subst InScopeSet
new_in_scope IdSubstEnv
new_env)
where
new_id :: Id
new_id = InScopeSet -> Id -> Id
uniqAway InScopeSet
in_scope Id
id
no_change :: Bool
no_change = Id
new_id Id -> Id -> Bool
forall a. Eq a => a -> a -> Bool
== Id
id
new_in_scope :: InScopeSet
new_in_scope = InScopeSet
in_scope InScopeSet -> Id -> InScopeSet
`extendInScopeSet` Id
new_id
new_env :: IdSubstEnv
new_env
| Bool
no_change = IdSubstEnv -> Id -> IdSubstEnv
forall a. VarEnv a -> Id -> VarEnv a
delVarEnv IdSubstEnv
env Id
id
| Bool
otherwise = IdSubstEnv -> Id -> Id -> IdSubstEnv
forall a. VarEnv a -> Id -> a -> VarEnv a
extendVarEnv IdSubstEnv
env Id
id Id
new_id
substBndrs :: Traversable f => f Id -> Subst -> (f Id, Subst)
substBndrs :: forall (f :: * -> *).
Traversable f =>
f Id -> Subst -> (f Id, Subst)
substBndrs = State Subst (f Id) -> Subst -> (f Id, Subst)
forall s a. State s a -> s -> (a, s)
runState (State Subst (f Id) -> Subst -> (f Id, Subst))
-> (f Id -> State Subst (f Id)) -> f Id -> Subst -> (f Id, Subst)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Id -> State Subst Id) -> f Id -> State Subst (f Id)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f b)
traverse ((Subst -> (Id, Subst)) -> State Subst Id
forall s a. (s -> (a, s)) -> State s a
state ((Subst -> (Id, Subst)) -> State Subst Id)
-> (Id -> Subst -> (Id, Subst)) -> Id -> State Subst Id
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> Subst -> (Id, Subst)
substBndr)
lookupIdSubst :: HasCallStack => Id -> Subst -> Id
lookupIdSubst :: HasCallStack => Id -> Subst -> Id
lookupIdSubst Id
id (Subst InScopeSet
in_scope IdSubstEnv
env)
| Bool -> Bool
not (Id -> Bool
isLocalId Id
id) = Id
id
| Just Id
id' <- IdSubstEnv -> Id -> Maybe Id
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv IdSubstEnv
env Id
id = Id
id'
| Just Id
id' <- InScopeSet -> Id -> Maybe Id
lookupInScope InScopeSet
in_scope Id
id = Id
id'
| Bool
otherwise = Bool -> String -> SDoc -> Id -> Id
forall a. HasCallStack => Bool -> String -> SDoc -> a -> a
warnPprTrace Bool
True String
"StgSubst.lookupIdSubst" (Id -> SDoc
forall a. Outputable a => a -> SDoc
ppr Id
id SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ InScopeSet -> SDoc
forall a. Outputable a => a -> SDoc
ppr InScopeSet
in_scope) Id
id
noWarnLookupIdSubst :: HasCallStack => Id -> Subst -> Id
noWarnLookupIdSubst :: HasCallStack => Id -> Subst -> Id
noWarnLookupIdSubst Id
id (Subst InScopeSet
in_scope IdSubstEnv
env)
| Bool -> Bool
not (Id -> Bool
isLocalId Id
id) = Id
id
| Just Id
id' <- IdSubstEnv -> Id -> Maybe Id
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv IdSubstEnv
env Id
id = Id
id'
| Just Id
id' <- InScopeSet -> Id -> Maybe Id
lookupInScope InScopeSet
in_scope Id
id = Id
id'
| Bool
otherwise = Id
id
extendInScope :: Id -> Subst -> Subst
extendInScope :: Id -> Subst -> Subst
extendInScope Id
id (Subst InScopeSet
in_scope IdSubstEnv
env) = InScopeSet -> IdSubstEnv -> Subst
Subst (InScopeSet
in_scope InScopeSet -> Id -> InScopeSet
`extendInScopeSet` Id
id) IdSubstEnv
env
extendSubst :: Id -> Id -> Subst -> Subst
extendSubst :: Id -> Id -> Subst -> Subst
extendSubst Id
id Id
new_id (Subst InScopeSet
in_scope IdSubstEnv
env)
= Bool -> SDoc -> Subst -> Subst
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Id
new_id Id -> InScopeSet -> Bool
`elemInScopeSet` InScopeSet
in_scope) (Id -> SDoc
forall a. Outputable a => a -> SDoc
ppr Id
id SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Id -> SDoc
forall a. Outputable a => a -> SDoc
ppr Id
new_id SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ InScopeSet -> SDoc
forall a. Outputable a => a -> SDoc
ppr InScopeSet
in_scope) (Subst -> Subst) -> Subst -> Subst
forall a b. (a -> b) -> a -> b
$
InScopeSet -> IdSubstEnv -> Subst
Subst InScopeSet
in_scope (IdSubstEnv -> Id -> Id -> IdSubstEnv
forall a. VarEnv a -> Id -> a -> VarEnv a
extendVarEnv IdSubstEnv
env Id
id Id
new_id)