{-# LANGUAGE TupleSections #-}
module GHC.StgToJS.ExprCtx
( ExprCtx
, initExprCtx
, ctxIsEvaluated
, ctxSetSrcSpan
, ctxSrcSpan
, ctxSetTop
, ctxTarget
, ctxSetTarget
, ctxClearLneFrame
, ctxUpdateLneFrame
, ctxLneFrameVars
, ctxLneFrameSize
, ctxIsLneBinding
, ctxIsLneLiveVar
, ctxLneBindingStackSize
, ctxLneShrinkStack
)
where
import GHC.Prelude
import GHC.StgToJS.Types
import GHC.Types.Unique.FM
import GHC.Types.Var
import GHC.Types.SrcLoc
import GHC.Types.Id
import GHC.Types.Id.Info
import GHC.Stg.EnforceEpt.TagSig
import GHC.Utils.Outputable
import GHC.Utils.Panic
import Data.Maybe
data ExprCtx = ExprCtx
{ ExprCtx -> Id
ctxTop :: Id
, ExprCtx -> [TypedExpr]
ctxTarget :: [TypedExpr]
, ExprCtx -> Maybe RealSrcSpan
ctxSrcSpan :: Maybe RealSrcSpan
, ExprCtx -> UniqFM Id Int
ctxLneFrameBs :: UniqFM Id Int
, ExprCtx -> [(Id, Int)]
ctxLneFrameVars :: [(Id,Int)]
, ExprCtx -> Int
ctxLneFrameSize :: {-# UNPACK #-} !Int
}
instance Outputable ExprCtx where
ppr :: ExprCtx -> SDoc
ppr ExprCtx
g = SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ExprCtx") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat
[ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ctxTop: ", Id -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ExprCtx -> Id
ctxTop ExprCtx
g)]
, [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ctxTarget:", [TypedExpr] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ExprCtx -> [TypedExpr]
ctxTarget ExprCtx
g)]
, [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ctxSrcSpan:", Maybe RealSrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ExprCtx -> Maybe RealSrcSpan
ctxSrcSpan ExprCtx
g)]
, [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ctxLneFrameBs:", UniqFM Id Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ExprCtx -> UniqFM Id Int
ctxLneFrameBs ExprCtx
g)]
, [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ctxLneFrameVars:", [(Id, Int)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ExprCtx -> [(Id, Int)]
ctxLneFrameVars ExprCtx
g)]
, [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ctxLneFrameSize:", Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ExprCtx -> Int
ctxLneFrameSize ExprCtx
g)]
]
initExprCtx :: Id -> ExprCtx
initExprCtx :: Id -> ExprCtx
initExprCtx Id
i = ExprCtx
{ ctxTop :: Id
ctxTop = Id
i
, ctxTarget :: [TypedExpr]
ctxTarget = []
, ctxLneFrameBs :: UniqFM Id Int
ctxLneFrameBs = UniqFM Id Int
forall {k} (key :: k) elt. UniqFM key elt
emptyUFM
, ctxLneFrameVars :: [(Id, Int)]
ctxLneFrameVars = []
, ctxLneFrameSize :: Int
ctxLneFrameSize = Int
0
, ctxSrcSpan :: Maybe RealSrcSpan
ctxSrcSpan = Maybe RealSrcSpan
forall a. Maybe a
Nothing
}
ctxSetTarget :: [TypedExpr] -> ExprCtx -> ExprCtx
ctxSetTarget :: [TypedExpr] -> ExprCtx -> ExprCtx
ctxSetTarget [TypedExpr]
t ExprCtx
ctx = ExprCtx
ctx { ctxTarget = t }
ctxSetTop :: Id -> ExprCtx -> ExprCtx
ctxSetTop :: Id -> ExprCtx -> ExprCtx
ctxSetTop Id
i ExprCtx
ctx = ExprCtx
ctx { ctxTop = i }
ctxSetSrcSpan :: RealSrcSpan -> ExprCtx -> ExprCtx
ctxSetSrcSpan :: RealSrcSpan -> ExprCtx -> ExprCtx
ctxSetSrcSpan RealSrcSpan
span ExprCtx
ctx = ExprCtx
ctx { ctxSrcSpan = Just span }
ctxUpdateLneFrame :: [(Id,Int)] -> [Id] -> ExprCtx -> ExprCtx
ctxUpdateLneFrame :: [(Id, Int)] -> [Id] -> ExprCtx -> ExprCtx
ctxUpdateLneFrame [(Id, Int)]
new_spilled_vars [Id]
new_lne_ids ExprCtx
ctx =
let old_frame_size :: Int
old_frame_size = ExprCtx -> Int
ctxLneFrameSize ExprCtx
ctx
new_frame_size :: Int
new_frame_size = Int
old_frame_size Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [(Id, Int)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Id, Int)]
new_spilled_vars
in ExprCtx
ctx
{ ctxLneFrameBs = addListToUFM (ctxLneFrameBs ctx) (map (,new_frame_size) new_lne_ids)
, ctxLneFrameSize = new_frame_size
, ctxLneFrameVars = ctxLneFrameVars ctx ++ new_spilled_vars
}
ctxClearLneFrame :: ExprCtx -> ExprCtx
ctxClearLneFrame :: ExprCtx -> ExprCtx
ctxClearLneFrame ExprCtx
ctx =
ExprCtx
ctx
{ ctxLneFrameBs = emptyUFM
, ctxLneFrameVars = []
, ctxLneFrameSize = 0
}
ctxIsEvaluated :: Id -> Bool
ctxIsEvaluated :: Id -> Bool
ctxIsEvaluated Id
i =
Bool -> (TagSig -> Bool) -> Maybe TagSig -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False TagSig -> Bool
isTaggedSig (Id -> Maybe TagSig
idTagSig_maybe Id
i)
Bool -> Bool -> Bool
&& IdDetails -> Bool
go (Id -> IdDetails
idDetails Id
i)
where
go :: IdDetails -> Bool
go JoinId{} = Bool
False
go IdDetails
_ = Bool
True
ctxIsLneBinding :: ExprCtx -> Id -> Bool
ctxIsLneBinding :: ExprCtx -> Id -> Bool
ctxIsLneBinding ExprCtx
ctx Id
i = Maybe Int -> Bool
forall a. Maybe a -> Bool
isJust (ExprCtx -> Id -> Maybe Int
ctxLneBindingStackSize ExprCtx
ctx Id
i)
ctxIsLneLiveVar :: ExprCtx -> Id -> Bool
ctxIsLneLiveVar :: ExprCtx -> Id -> Bool
ctxIsLneLiveVar ExprCtx
ctx Id
i = Id
i Id -> [Id] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ((Id, Int) -> Id) -> [(Id, Int)] -> [Id]
forall a b. (a -> b) -> [a] -> [b]
map (Id, Int) -> Id
forall a b. (a, b) -> a
fst (ExprCtx -> [(Id, Int)]
ctxLneFrameVars ExprCtx
ctx)
ctxLneBindingStackSize :: ExprCtx -> Id -> Maybe Int
ctxLneBindingStackSize :: ExprCtx -> Id -> Maybe Int
ctxLneBindingStackSize ExprCtx
ctx Id
i = UniqFM Id Int -> Id -> Maybe Int
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM (ExprCtx -> UniqFM Id Int
ctxLneFrameBs ExprCtx
ctx) Id
i
ctxLneShrinkStack :: ExprCtx -> Int -> ExprCtx
ctxLneShrinkStack :: ExprCtx -> Int -> ExprCtx
ctxLneShrinkStack ExprCtx
ctx Int
n =
let l :: Int
l = ExprCtx -> Int
ctxLneFrameSize ExprCtx
ctx
in Bool -> SDoc -> ExprCtx -> ExprCtx
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr
(Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n)
([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ctxLneShrinkStack: let-no-escape stack too short:"
, Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
l
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
" < "
, Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
n
])
(ExprCtx
ctx { ctxLneFrameVars = take n (ctxLneFrameVars ctx)
, ctxLneFrameSize = n
}
)