{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiWayIf #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Cmm.DebugBlock (
DebugBlock(..),
cmmDebugGen,
cmmDebugLabels,
cmmDebugLink,
debugToMap,
UnwindTable, UnwindPoint(..),
UnwindExpr(..), toUnwindExpr
) where
import GHC.Prelude
import GHC.Platform
import GHC.Cmm.BlockId
import GHC.Cmm.CLabel
import GHC.Cmm
import GHC.Cmm.Utils
import GHC.Core
import GHC.Data.FastString ( nilFS, mkFastString )
import GHC.Unit.Module
import GHC.Utils.Outputable
import GHC.Cmm.Ppr.Expr ( pprExpr )
import GHC.Types.SrcLoc
import GHC.Utils.Misc ( seqList )
import GHC.Cmm.Dataflow.Block
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Graph
import GHC.Cmm.Dataflow.Label
import Data.Maybe
import Data.List ( minimumBy, nubBy )
import Data.Ord ( comparing )
import qualified Data.Map as Map
import Data.Either ( partitionEithers )
data DebugBlock =
DebugBlock
{ DebugBlock -> Label
dblProcedure :: !Label
, DebugBlock -> Label
dblLabel :: !Label
, DebugBlock -> CLabel
dblCLabel :: !CLabel
, DebugBlock -> Bool
dblHasInfoTbl :: !Bool
, DebugBlock -> Maybe DebugBlock
dblParent :: !(Maybe DebugBlock)
, DebugBlock -> [Tickish ()]
dblTicks :: ![CmmTickish]
, DebugBlock -> Maybe (Tickish ())
dblSourceTick :: !(Maybe CmmTickish)
, DebugBlock -> Maybe Int
dblPosition :: !(Maybe Int)
, DebugBlock -> [UnwindPoint]
dblUnwind :: [UnwindPoint]
, DebugBlock -> [DebugBlock]
dblBlocks :: ![DebugBlock]
}
instance Outputable DebugBlock where
ppr :: DebugBlock -> SDoc
ppr DebugBlock
blk = (if | DebugBlock -> Label
dblProcedure DebugBlock
blk Label -> Label -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Label
== DebugBlock -> Label
dblLabel DebugBlock
blk
-> String -> SDoc
text String
"proc"
| DebugBlock -> Bool
dblHasInfoTbl DebugBlock
blk
-> String -> SDoc
text String
"pp-blk"
| Bool
otherwise
-> String -> SDoc
text String
"blk") SDoc -> SDoc -> SDoc
<+>
Label -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Label
ppr (DebugBlock -> Label
dblLabel DebugBlock
blk) SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (CLabel -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable CLabel
ppr (DebugBlock -> CLabel
dblCLabel DebugBlock
blk)) SDoc -> SDoc -> SDoc
<+>
(SDoc -> (Tickish () -> SDoc) -> Maybe (Tickish ()) -> SDoc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SDoc
empty Tickish () -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall id. Outputable id => Outputable (Tickish id)
External instance of the constraint type Outputable ()
ppr (DebugBlock -> Maybe (Tickish ())
dblSourceTick DebugBlock
blk)) SDoc -> SDoc -> SDoc
<+>
(SDoc -> (Int -> SDoc) -> Maybe Int -> SDoc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> SDoc
text String
"removed") ((String -> SDoc
text String
"pos " SDoc -> SDoc -> SDoc
<>) (SDoc -> SDoc) -> (Int -> SDoc) -> Int -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Int
ppr)
(DebugBlock -> Maybe Int
dblPosition DebugBlock
blk)) SDoc -> SDoc -> SDoc
<+>
([UnwindPoint] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
Instance of class: Outputable of the constraint type Outputable UnwindPoint
ppr (DebugBlock -> [UnwindPoint]
dblUnwind DebugBlock
blk)) SDoc -> SDoc -> SDoc
$+$
(if [DebugBlock] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null (DebugBlock -> [DebugBlock]
dblBlocks DebugBlock
blk) then SDoc
empty else Int -> SDoc -> SDoc
nest Int
4 ([DebugBlock] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
Instance of class: Outputable of the constraint type Outputable DebugBlock
ppr (DebugBlock -> [DebugBlock]
dblBlocks DebugBlock
blk)))
type BlockContext = (CmmBlock, RawCmmDecl)
cmmDebugGen :: ModLocation -> RawCmmGroup -> [DebugBlock]
cmmDebugGen :: ModLocation -> RawCmmGroup -> [DebugBlock]
cmmDebugGen ModLocation
modLoc RawCmmGroup
decls = (CmmTickScope -> DebugBlock) -> [CmmTickScope] -> [DebugBlock]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe (Tickish ()) -> CmmTickScope -> DebugBlock
blocksForScope Maybe (Tickish ())
forall a. Maybe a
Nothing) [CmmTickScope]
topScopes
where
blockCtxs :: Map.Map CmmTickScope [BlockContext]
blockCtxs :: Map CmmTickScope [BlockContext]
blockCtxs = RawCmmGroup -> Map CmmTickScope [BlockContext]
blockContexts RawCmmGroup
decls
([CmmTickScope]
topScopes, [(CmmTickScope, CmmTickScope)]
childScopes)
= [Either CmmTickScope (CmmTickScope, CmmTickScope)]
-> ([CmmTickScope], [(CmmTickScope, CmmTickScope)])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either CmmTickScope (CmmTickScope, CmmTickScope)]
-> ([CmmTickScope], [(CmmTickScope, CmmTickScope)]))
-> [Either CmmTickScope (CmmTickScope, CmmTickScope)]
-> ([CmmTickScope], [(CmmTickScope, CmmTickScope)])
forall a b. (a -> b) -> a -> b
$ (CmmTickScope -> Either CmmTickScope (CmmTickScope, CmmTickScope))
-> [CmmTickScope]
-> [Either CmmTickScope (CmmTickScope, CmmTickScope)]
forall a b. (a -> b) -> [a] -> [b]
map (\CmmTickScope
a -> CmmTickScope
-> CmmTickScope -> Either CmmTickScope (CmmTickScope, CmmTickScope)
forall {t}. t -> CmmTickScope -> Either t (CmmTickScope, t)
findP CmmTickScope
a CmmTickScope
a) ([CmmTickScope]
-> [Either CmmTickScope (CmmTickScope, CmmTickScope)])
-> [CmmTickScope]
-> [Either CmmTickScope (CmmTickScope, CmmTickScope)]
forall a b. (a -> b) -> a -> b
$ Map CmmTickScope [BlockContext] -> [CmmTickScope]
forall k a. Map k a -> [k]
Map.keys Map CmmTickScope [BlockContext]
blockCtxs
findP :: t -> CmmTickScope -> Either t (CmmTickScope, t)
findP t
tsc CmmTickScope
GlobalScope = t -> Either t (CmmTickScope, t)
forall a b. a -> Either a b
Left t
tsc
findP t
tsc CmmTickScope
scp | CmmTickScope
scp' CmmTickScope -> Map CmmTickScope [BlockContext] -> Bool
forall k a. Ord k => k -> Map k a -> Bool
External instance of the constraint type Ord CmmTickScope
`Map.member` Map CmmTickScope [BlockContext]
blockCtxs = (CmmTickScope, t) -> Either t (CmmTickScope, t)
forall a b. b -> Either a b
Right (CmmTickScope
scp', t
tsc)
| Bool
otherwise = t -> CmmTickScope -> Either t (CmmTickScope, t)
findP t
tsc CmmTickScope
scp'
where
scp' :: CmmTickScope
scp' | SubScope Unique
_ CmmTickScope
scp' <- CmmTickScope
scp = CmmTickScope
scp'
| CombinedScope CmmTickScope
scp' CmmTickScope
_ <- CmmTickScope
scp = CmmTickScope
scp'
| Bool
otherwise = String -> CmmTickScope
forall a. String -> a
panic String
"findP impossible"
scopeMap :: Map CmmTickScope [CmmTickScope]
scopeMap = ((CmmTickScope, CmmTickScope)
-> Map CmmTickScope [CmmTickScope]
-> Map CmmTickScope [CmmTickScope])
-> Map CmmTickScope [CmmTickScope]
-> [(CmmTickScope, CmmTickScope)]
-> Map CmmTickScope [CmmTickScope]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr ((CmmTickScope
-> CmmTickScope
-> Map CmmTickScope [CmmTickScope]
-> Map CmmTickScope [CmmTickScope])
-> (CmmTickScope, CmmTickScope)
-> Map CmmTickScope [CmmTickScope]
-> Map CmmTickScope [CmmTickScope]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry CmmTickScope
-> CmmTickScope
-> Map CmmTickScope [CmmTickScope]
-> Map CmmTickScope [CmmTickScope]
forall k a. Ord k => k -> a -> Map k [a] -> Map k [a]
External instance of the constraint type Ord CmmTickScope
insertMulti) Map CmmTickScope [CmmTickScope]
forall k a. Map k a
Map.empty [(CmmTickScope, CmmTickScope)]
childScopes
ticksToCopy :: CmmTickScope -> [CmmTickish]
ticksToCopy :: CmmTickScope -> [Tickish ()]
ticksToCopy (CombinedScope CmmTickScope
scp CmmTickScope
s) = CmmTickScope -> [Tickish ()]
go CmmTickScope
s
where go :: CmmTickScope -> [Tickish ()]
go CmmTickScope
s | CmmTickScope
scp CmmTickScope -> CmmTickScope -> Bool
`isTickSubScope` CmmTickScope
s = []
| SubScope Unique
_ CmmTickScope
s' <- CmmTickScope
s = [Tickish ()]
ticks [Tickish ()] -> [Tickish ()] -> [Tickish ()]
forall a. [a] -> [a] -> [a]
++ CmmTickScope -> [Tickish ()]
go CmmTickScope
s'
| CombinedScope CmmTickScope
s1 CmmTickScope
s2 <- CmmTickScope
s = [Tickish ()]
ticks [Tickish ()] -> [Tickish ()] -> [Tickish ()]
forall a. [a] -> [a] -> [a]
++ CmmTickScope -> [Tickish ()]
go CmmTickScope
s1 [Tickish ()] -> [Tickish ()] -> [Tickish ()]
forall a. [a] -> [a] -> [a]
++ CmmTickScope -> [Tickish ()]
go CmmTickScope
s2
| Bool
otherwise = String -> [Tickish ()]
forall a. String -> a
panic String
"ticksToCopy impossible"
where ticks :: [Tickish ()]
ticks = [BlockContext] -> [Tickish ()]
forall {b}. [(Block CmmNode C C, b)] -> [Tickish ()]
bCtxsTicks ([BlockContext] -> [Tickish ()]) -> [BlockContext] -> [Tickish ()]
forall a b. (a -> b) -> a -> b
$ [BlockContext] -> Maybe [BlockContext] -> [BlockContext]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [BlockContext] -> [BlockContext])
-> Maybe [BlockContext] -> [BlockContext]
forall a b. (a -> b) -> a -> b
$ CmmTickScope
-> Map CmmTickScope [BlockContext] -> Maybe [BlockContext]
forall k a. Ord k => k -> Map k a -> Maybe a
External instance of the constraint type Ord CmmTickScope
Map.lookup CmmTickScope
s Map CmmTickScope [BlockContext]
blockCtxs
ticksToCopy CmmTickScope
_ = []
bCtxsTicks :: [(Block CmmNode C C, b)] -> [Tickish ()]
bCtxsTicks = ((Block CmmNode C C, b) -> [Tickish ()])
-> [(Block CmmNode C C, b)] -> [Tickish ()]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
External instance of the constraint type Foldable []
concatMap (Block CmmNode C C -> [Tickish ()]
blockTicks (Block CmmNode C C -> [Tickish ()])
-> ((Block CmmNode C C, b) -> Block CmmNode C C)
-> (Block CmmNode C C, b)
-> [Tickish ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Block CmmNode C C, b) -> Block CmmNode C C
forall a b. (a, b) -> a
fst)
bestSrcTick :: [Tickish ()] -> Tickish ()
bestSrcTick = (Tickish () -> Tickish () -> Ordering)
-> [Tickish ()] -> Tickish ()
forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
External instance of the constraint type Foldable []
minimumBy ((Tickish () -> Int) -> Tickish () -> Tickish () -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
External instance of the constraint type Ord Int
comparing Tickish () -> Int
rangeRating)
rangeRating :: Tickish () -> Int
rangeRating (SourceNote RealSrcSpan
span String
_)
| RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq FastString
== FastString
thisFile = Int
1
| Bool
otherwise = Int
2 :: Int
rangeRating Tickish ()
note = String -> SDoc -> Int
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"rangeRating" (Tickish () -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall id. Outputable id => Outputable (Tickish id)
External instance of the constraint type Outputable ()
ppr Tickish ()
note)
thisFile :: FastString
thisFile = FastString -> (String -> FastString) -> Maybe String -> FastString
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FastString
nilFS String -> FastString
mkFastString (Maybe String -> FastString) -> Maybe String -> FastString
forall a b. (a -> b) -> a -> b
$ ModLocation -> Maybe String
ml_hs_file ModLocation
modLoc
blocksForScope :: Maybe CmmTickish -> CmmTickScope -> DebugBlock
blocksForScope :: Maybe (Tickish ()) -> CmmTickScope -> DebugBlock
blocksForScope Maybe (Tickish ())
cstick CmmTickScope
scope = Bool -> BlockContext -> DebugBlock
mkBlock Bool
True ([BlockContext] -> BlockContext
forall a. [a] -> a
head [BlockContext]
bctxs)
where bctxs :: [BlockContext]
bctxs = Maybe [BlockContext] -> [BlockContext]
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe [BlockContext] -> [BlockContext])
-> Maybe [BlockContext] -> [BlockContext]
forall a b. (a -> b) -> a -> b
$ CmmTickScope
-> Map CmmTickScope [BlockContext] -> Maybe [BlockContext]
forall k a. Ord k => k -> Map k a -> Maybe a
External instance of the constraint type Ord CmmTickScope
Map.lookup CmmTickScope
scope Map CmmTickScope [BlockContext]
blockCtxs
nested :: [CmmTickScope]
nested = [CmmTickScope] -> Maybe [CmmTickScope] -> [CmmTickScope]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [CmmTickScope] -> [CmmTickScope])
-> Maybe [CmmTickScope] -> [CmmTickScope]
forall a b. (a -> b) -> a -> b
$ CmmTickScope
-> Map CmmTickScope [CmmTickScope] -> Maybe [CmmTickScope]
forall k a. Ord k => k -> Map k a -> Maybe a
External instance of the constraint type Ord CmmTickScope
Map.lookup CmmTickScope
scope Map CmmTickScope [CmmTickScope]
scopeMap
childs :: [DebugBlock]
childs = (BlockContext -> DebugBlock) -> [BlockContext] -> [DebugBlock]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> BlockContext -> DebugBlock
mkBlock Bool
False) ([BlockContext] -> [BlockContext]
forall a. [a] -> [a]
tail [BlockContext]
bctxs) [DebugBlock] -> [DebugBlock] -> [DebugBlock]
forall a. [a] -> [a] -> [a]
++
(CmmTickScope -> DebugBlock) -> [CmmTickScope] -> [DebugBlock]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe (Tickish ()) -> CmmTickScope -> DebugBlock
blocksForScope Maybe (Tickish ())
stick) [CmmTickScope]
nested
mkBlock :: Bool -> BlockContext -> DebugBlock
mkBlock :: Bool -> BlockContext -> DebugBlock
mkBlock Bool
top (Block CmmNode C C
block, RawCmmDecl
prc)
= DebugBlock :: Label
-> Label
-> CLabel
-> Bool
-> Maybe DebugBlock
-> [Tickish ()]
-> Maybe (Tickish ())
-> Maybe Int
-> [UnwindPoint]
-> [DebugBlock]
-> DebugBlock
DebugBlock { dblProcedure :: Label
dblProcedure = GenCmmGraph CmmNode -> Label
forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> Label
g_entry GenCmmGraph CmmNode
graph
, dblLabel :: Label
dblLabel = Label
label
, dblCLabel :: CLabel
dblCLabel = case Maybe RawCmmStatics
info of
Just (CmmStaticsRaw CLabel
infoLbl [CmmStatic]
_) -> CLabel
infoLbl
Maybe RawCmmStatics
Nothing
| GenCmmGraph CmmNode -> Label
forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> Label
g_entry GenCmmGraph CmmNode
graph Label -> Label -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Label
== Label
label -> CLabel
entryLbl
| Bool
otherwise -> Label -> CLabel
blockLbl Label
label
, dblHasInfoTbl :: Bool
dblHasInfoTbl = Maybe RawCmmStatics -> Bool
forall a. Maybe a -> Bool
isJust Maybe RawCmmStatics
info
, dblParent :: Maybe DebugBlock
dblParent = Maybe DebugBlock
forall a. Maybe a
Nothing
, dblTicks :: [Tickish ()]
dblTicks = [Tickish ()]
ticks
, dblPosition :: Maybe Int
dblPosition = Maybe Int
forall a. Maybe a
Nothing
, dblSourceTick :: Maybe (Tickish ())
dblSourceTick = Maybe (Tickish ())
stick
, dblBlocks :: [DebugBlock]
dblBlocks = [DebugBlock]
blocks
, dblUnwind :: [UnwindPoint]
dblUnwind = []
}
where (CmmProc LabelMap RawCmmStatics
infos CLabel
entryLbl [GlobalReg]
_ GenCmmGraph CmmNode
graph) = RawCmmDecl
prc
label :: Label
label = Block CmmNode C C -> Label
forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> Label
External instance of the constraint type forall (n :: Extensibility -> Extensibility -> *).
NonLocal n =>
NonLocal (Block n)
External instance of the constraint type NonLocal CmmNode
entryLabel Block CmmNode C C
block
info :: Maybe RawCmmStatics
info = KeyOf LabelMap -> LabelMap RawCmmStatics -> Maybe RawCmmStatics
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
External instance of the constraint type IsMap LabelMap
mapLookup KeyOf LabelMap
Label
label LabelMap RawCmmStatics
infos
blocks :: [DebugBlock]
blocks | Bool
top = [DebugBlock] -> [DebugBlock] -> [DebugBlock]
forall a b. [a] -> b -> b
seqList [DebugBlock]
childs [DebugBlock]
childs
| Bool
otherwise = []
isSourceTick :: Tickish id -> Bool
isSourceTick SourceNote {} = Bool
True
isSourceTick Tickish id
_ = Bool
False
ticks :: [Tickish ()]
ticks = (Tickish () -> Tickish () -> Bool) -> [Tickish ()] -> [Tickish ()]
forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy ((Tickish () -> Tickish () -> Bool)
-> Tickish () -> Tickish () -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Tickish () -> Tickish () -> Bool
forall b. Eq b => Tickish b -> Tickish b -> Bool
External instance of the constraint type Eq ()
tickishContains) ([Tickish ()] -> [Tickish ()]) -> [Tickish ()] -> [Tickish ()]
forall a b. (a -> b) -> a -> b
$
[BlockContext] -> [Tickish ()]
forall {b}. [(Block CmmNode C C, b)] -> [Tickish ()]
bCtxsTicks [BlockContext]
bctxs [Tickish ()] -> [Tickish ()] -> [Tickish ()]
forall a. [a] -> [a] -> [a]
++ CmmTickScope -> [Tickish ()]
ticksToCopy CmmTickScope
scope
stick :: Maybe (Tickish ())
stick = case (Tickish () -> Bool) -> [Tickish ()] -> [Tickish ()]
forall a. (a -> Bool) -> [a] -> [a]
filter Tickish () -> Bool
forall {id}. Tickish id -> Bool
isSourceTick [Tickish ()]
ticks of
[] -> Maybe (Tickish ())
cstick
[Tickish ()]
sticks -> Tickish () -> Maybe (Tickish ())
forall a. a -> Maybe a
Just (Tickish () -> Maybe (Tickish ()))
-> Tickish () -> Maybe (Tickish ())
forall a b. (a -> b) -> a -> b
$! [Tickish ()] -> Tickish ()
bestSrcTick ([Tickish ()]
sticks [Tickish ()] -> [Tickish ()] -> [Tickish ()]
forall a. [a] -> [a] -> [a]
++ Maybe (Tickish ()) -> [Tickish ()]
forall a. Maybe a -> [a]
maybeToList Maybe (Tickish ())
cstick)
blockContexts :: RawCmmGroup -> Map.Map CmmTickScope [BlockContext]
blockContexts :: RawCmmGroup -> Map CmmTickScope [BlockContext]
blockContexts RawCmmGroup
decls = ([BlockContext] -> [BlockContext])
-> Map CmmTickScope [BlockContext]
-> Map CmmTickScope [BlockContext]
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map [BlockContext] -> [BlockContext]
forall a. [a] -> [a]
reverse (Map CmmTickScope [BlockContext]
-> Map CmmTickScope [BlockContext])
-> Map CmmTickScope [BlockContext]
-> Map CmmTickScope [BlockContext]
forall a b. (a -> b) -> a -> b
$ (RawCmmDecl
-> Map CmmTickScope [BlockContext]
-> Map CmmTickScope [BlockContext])
-> Map CmmTickScope [BlockContext]
-> RawCmmGroup
-> Map CmmTickScope [BlockContext]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr RawCmmDecl
-> Map CmmTickScope [BlockContext]
-> Map CmmTickScope [BlockContext]
walkProc Map CmmTickScope [BlockContext]
forall k a. Map k a
Map.empty RawCmmGroup
decls
where walkProc :: RawCmmDecl
-> Map.Map CmmTickScope [BlockContext]
-> Map.Map CmmTickScope [BlockContext]
walkProc :: RawCmmDecl
-> Map CmmTickScope [BlockContext]
-> Map CmmTickScope [BlockContext]
walkProc CmmData{} Map CmmTickScope [BlockContext]
m = Map CmmTickScope [BlockContext]
m
walkProc prc :: RawCmmDecl
prc@(CmmProc LabelMap RawCmmStatics
_ CLabel
_ [GlobalReg]
_ GenCmmGraph CmmNode
graph) Map CmmTickScope [BlockContext]
m
| LabelMap (Block CmmNode C C) -> Bool
forall (map :: * -> *) a. IsMap map => map a -> Bool
External instance of the constraint type IsMap LabelMap
mapNull LabelMap (Block CmmNode C C)
blocks = Map CmmTickScope [BlockContext]
m
| Bool
otherwise = (LabelSet, Map CmmTickScope [BlockContext])
-> Map CmmTickScope [BlockContext]
forall a b. (a, b) -> b
snd ((LabelSet, Map CmmTickScope [BlockContext])
-> Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext])
-> Map CmmTickScope [BlockContext]
forall a b. (a -> b) -> a -> b
$ RawCmmDecl
-> [Block CmmNode C C]
-> (LabelSet, Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext])
walkBlock RawCmmDecl
prc [Block CmmNode C C]
entry (LabelSet
emptyLbls, Map CmmTickScope [BlockContext]
m)
where blocks :: LabelMap (Block CmmNode C C)
blocks = GenCmmGraph CmmNode -> LabelMap (Block CmmNode C C)
toBlockMap GenCmmGraph CmmNode
graph
entry :: [Block CmmNode C C]
entry = [KeyOf LabelMap -> LabelMap (Block CmmNode C C) -> Block CmmNode C C
forall {a}. KeyOf LabelMap -> LabelMap a -> a
mapFind (GenCmmGraph CmmNode -> Label
forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> Label
g_entry GenCmmGraph CmmNode
graph) LabelMap (Block CmmNode C C)
blocks]
emptyLbls :: LabelSet
emptyLbls = LabelSet
forall set. IsSet set => set
External instance of the constraint type IsSet LabelSet
setEmpty :: LabelSet
walkBlock :: RawCmmDecl -> [Block CmmNode C C]
-> (LabelSet, Map.Map CmmTickScope [BlockContext])
-> (LabelSet, Map.Map CmmTickScope [BlockContext])
walkBlock :: RawCmmDecl
-> [Block CmmNode C C]
-> (LabelSet, Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext])
walkBlock RawCmmDecl
_ [] (LabelSet, Map CmmTickScope [BlockContext])
c = (LabelSet, Map CmmTickScope [BlockContext])
c
walkBlock RawCmmDecl
prc (Block CmmNode C C
block:[Block CmmNode C C]
blocks) (LabelSet
visited, Map CmmTickScope [BlockContext]
m)
| ElemOf LabelSet
Label
lbl ElemOf LabelSet -> LabelSet -> Bool
forall set. IsSet set => ElemOf set -> set -> Bool
External instance of the constraint type IsSet LabelSet
`setMember` LabelSet
visited
= RawCmmDecl
-> [Block CmmNode C C]
-> (LabelSet, Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext])
walkBlock RawCmmDecl
prc [Block CmmNode C C]
blocks (LabelSet
visited, Map CmmTickScope [BlockContext]
m)
| Bool
otherwise
= RawCmmDecl
-> [Block CmmNode C C]
-> (LabelSet, Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext])
walkBlock RawCmmDecl
prc [Block CmmNode C C]
blocks ((LabelSet, Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext]))
-> (LabelSet, Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext])
forall a b. (a -> b) -> a -> b
$
RawCmmDecl
-> [Block CmmNode C C]
-> (LabelSet, Map CmmTickScope [BlockContext])
-> (LabelSet, Map CmmTickScope [BlockContext])
walkBlock RawCmmDecl
prc [Block CmmNode C C]
succs
(ElemOf LabelSet
Label
lbl ElemOf LabelSet -> LabelSet -> LabelSet
forall set. IsSet set => ElemOf set -> set -> set
External instance of the constraint type IsSet LabelSet
`setInsert` LabelSet
visited,
CmmTickScope
-> BlockContext
-> Map CmmTickScope [BlockContext]
-> Map CmmTickScope [BlockContext]
forall k a. Ord k => k -> a -> Map k [a] -> Map k [a]
External instance of the constraint type Ord CmmTickScope
insertMulti CmmTickScope
scope (Block CmmNode C C
block, RawCmmDecl
prc) Map CmmTickScope [BlockContext]
m)
where CmmEntry Label
lbl CmmTickScope
scope = Block CmmNode C C -> CmmNode C O
forall (n :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
Block n C x -> n C O
firstNode Block CmmNode C C
block
(CmmProc LabelMap RawCmmStatics
_ CLabel
_ [GlobalReg]
_ GenCmmGraph CmmNode
graph) = RawCmmDecl
prc
succs :: [Block CmmNode C C]
succs = (Label -> Block CmmNode C C) -> [Label] -> [Block CmmNode C C]
forall a b. (a -> b) -> [a] -> [b]
map ((Label -> LabelMap (Block CmmNode C C) -> Block CmmNode C C)
-> LabelMap (Block CmmNode C C) -> Label -> Block CmmNode C C
forall a b c. (a -> b -> c) -> b -> a -> c
flip Label -> LabelMap (Block CmmNode C C) -> Block CmmNode C C
forall {a}. KeyOf LabelMap -> LabelMap a -> a
mapFind (GenCmmGraph CmmNode -> LabelMap (Block CmmNode C C)
toBlockMap GenCmmGraph CmmNode
graph))
(CmmNode O C -> [Label]
forall (thing :: Extensibility -> Extensibility -> *)
(e :: Extensibility).
NonLocal thing =>
thing e C -> [Label]
External instance of the constraint type NonLocal CmmNode
successors (Block CmmNode C C -> CmmNode O C
forall (n :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
Block n x C -> n O C
lastNode Block CmmNode C C
block))
mapFind :: KeyOf LabelMap -> LabelMap a -> a
mapFind = a -> KeyOf LabelMap -> LabelMap a -> a
forall (map :: * -> *) a. IsMap map => a -> KeyOf map -> map a -> a
External instance of the constraint type IsMap LabelMap
mapFindWithDefault (String -> a
forall a. HasCallStack => String -> a
error String
"contextTree: block not found!")
insertMulti :: Ord k => k -> a -> Map.Map k [a] -> Map.Map k [a]
insertMulti :: k -> a -> Map k [a] -> Map k [a]
insertMulti k
k a
v = ([a] -> [a] -> [a]) -> k -> [a] -> Map k [a] -> Map k [a]
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
Map.insertWith (([a] -> [a]) -> [a] -> [a] -> [a]
forall a b. a -> b -> a
const (a
va -> [a] -> [a]
forall a. a -> [a] -> [a]
:)) k
k [a
v]
cmmDebugLabels :: (i -> Bool) -> GenCmmGroup d g (ListGraph i) -> [Label]
cmmDebugLabels :: (i -> Bool) -> GenCmmGroup d g (ListGraph i) -> [Label]
cmmDebugLabels i -> Bool
isMeta GenCmmGroup d g (ListGraph i)
nats = [Label] -> [Label] -> [Label]
forall a b. [a] -> b -> b
seqList [Label]
lbls [Label]
lbls
where
lbls :: [Label]
lbls = (GenBasicBlock i -> Label) -> [GenBasicBlock i] -> [Label]
forall a b. (a -> b) -> [a] -> [b]
map GenBasicBlock i -> Label
forall i. GenBasicBlock i -> Label
blockId ([GenBasicBlock i] -> [Label]) -> [GenBasicBlock i] -> [Label]
forall a b. (a -> b) -> a -> b
$ (GenBasicBlock i -> Bool) -> [GenBasicBlock i] -> [GenBasicBlock i]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (GenBasicBlock i -> Bool) -> GenBasicBlock i -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenBasicBlock i -> Bool
allMeta) ([GenBasicBlock i] -> [GenBasicBlock i])
-> [GenBasicBlock i] -> [GenBasicBlock i]
forall a b. (a -> b) -> a -> b
$ (GenCmmDecl d g (ListGraph i) -> [GenBasicBlock i])
-> GenCmmGroup d g (ListGraph i) -> [GenBasicBlock i]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
External instance of the constraint type Foldable []
concatMap GenCmmDecl d g (ListGraph i) -> [GenBasicBlock i]
forall {d} {h} {i}.
GenCmmDecl d h (ListGraph i) -> [GenBasicBlock i]
getBlocks GenCmmGroup d g (ListGraph i)
nats
getBlocks :: GenCmmDecl d h (ListGraph i) -> [GenBasicBlock i]
getBlocks (CmmProc h
_ CLabel
_ [GlobalReg]
_ (ListGraph [GenBasicBlock i]
bs)) = [GenBasicBlock i]
bs
getBlocks GenCmmDecl d h (ListGraph i)
_other = []
allMeta :: GenBasicBlock i -> Bool
allMeta (BasicBlock Label
_ [i]
instrs) = (i -> Bool) -> [i] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
all i -> Bool
isMeta [i]
instrs
cmmDebugLink :: [Label] -> LabelMap [UnwindPoint]
-> [DebugBlock] -> [DebugBlock]
cmmDebugLink :: [Label] -> LabelMap [UnwindPoint] -> [DebugBlock] -> [DebugBlock]
cmmDebugLink [Label]
labels LabelMap [UnwindPoint]
unwindPts [DebugBlock]
blocks = (DebugBlock -> DebugBlock) -> [DebugBlock] -> [DebugBlock]
forall a b. (a -> b) -> [a] -> [b]
map DebugBlock -> DebugBlock
link [DebugBlock]
blocks
where blockPos :: LabelMap Int
blockPos :: LabelMap Int
blockPos = [(KeyOf LabelMap, Int)] -> LabelMap Int
forall (map :: * -> *) a. IsMap map => [(KeyOf map, a)] -> map a
External instance of the constraint type IsMap LabelMap
mapFromList ([(KeyOf LabelMap, Int)] -> LabelMap Int)
-> [(KeyOf LabelMap, Int)] -> LabelMap Int
forall a b. (a -> b) -> a -> b
$ ([Label] -> [Int] -> [(Label, Int)])
-> [Int] -> [Label] -> [(Label, Int)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip [Label] -> [Int] -> [(Label, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [Label]
labels
link :: DebugBlock -> DebugBlock
link DebugBlock
block = DebugBlock
block { dblPosition :: Maybe Int
dblPosition = KeyOf LabelMap -> LabelMap Int -> Maybe Int
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
External instance of the constraint type IsMap LabelMap
mapLookup (DebugBlock -> Label
dblLabel DebugBlock
block) LabelMap Int
blockPos
, dblBlocks :: [DebugBlock]
dblBlocks = (DebugBlock -> DebugBlock) -> [DebugBlock] -> [DebugBlock]
forall a b. (a -> b) -> [a] -> [b]
map DebugBlock -> DebugBlock
link (DebugBlock -> [DebugBlock]
dblBlocks DebugBlock
block)
, dblUnwind :: [UnwindPoint]
dblUnwind = [UnwindPoint] -> Maybe [UnwindPoint] -> [UnwindPoint]
forall a. a -> Maybe a -> a
fromMaybe [UnwindPoint]
forall a. Monoid a => a
External instance of the constraint type forall a. Monoid [a]
mempty
(Maybe [UnwindPoint] -> [UnwindPoint])
-> Maybe [UnwindPoint] -> [UnwindPoint]
forall a b. (a -> b) -> a -> b
$ KeyOf LabelMap -> LabelMap [UnwindPoint] -> Maybe [UnwindPoint]
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
External instance of the constraint type IsMap LabelMap
mapLookup (DebugBlock -> Label
dblLabel DebugBlock
block) LabelMap [UnwindPoint]
unwindPts
}
debugToMap :: [DebugBlock] -> LabelMap DebugBlock
debugToMap :: [DebugBlock] -> LabelMap DebugBlock
debugToMap = [LabelMap DebugBlock] -> LabelMap DebugBlock
forall (map :: * -> *) a. IsMap map => [map a] -> map a
External instance of the constraint type IsMap LabelMap
mapUnions ([LabelMap DebugBlock] -> LabelMap DebugBlock)
-> ([DebugBlock] -> [LabelMap DebugBlock])
-> [DebugBlock]
-> LabelMap DebugBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DebugBlock -> LabelMap DebugBlock)
-> [DebugBlock] -> [LabelMap DebugBlock]
forall a b. (a -> b) -> [a] -> [b]
map DebugBlock -> LabelMap DebugBlock
forall {map :: * -> *}.
(IsMap map, KeyOf map ~ Label) =>
DebugBlock -> map DebugBlock
External instance of the constraint type IsMap LabelMap
go
where go :: DebugBlock -> map DebugBlock
go DebugBlock
b = KeyOf map -> DebugBlock -> map DebugBlock -> map DebugBlock
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
Evidence bound by a type signature of the constraint type IsMap map
mapInsert (DebugBlock -> Label
dblLabel DebugBlock
b) DebugBlock
b (map DebugBlock -> map DebugBlock)
-> map DebugBlock -> map DebugBlock
forall a b. (a -> b) -> a -> b
$ [map DebugBlock] -> map DebugBlock
forall (map :: * -> *) a. IsMap map => [map a] -> map a
Evidence bound by a type signature of the constraint type IsMap map
mapUnions ([map DebugBlock] -> map DebugBlock)
-> [map DebugBlock] -> map DebugBlock
forall a b. (a -> b) -> a -> b
$ (DebugBlock -> map DebugBlock) -> [DebugBlock] -> [map DebugBlock]
forall a b. (a -> b) -> [a] -> [b]
map DebugBlock -> map DebugBlock
go (DebugBlock -> [DebugBlock]
dblBlocks DebugBlock
b)
data UnwindPoint = UnwindPoint !CLabel !UnwindTable
instance Outputable UnwindPoint where
ppr :: UnwindPoint -> SDoc
ppr (UnwindPoint CLabel
lbl UnwindTable
uws) =
SDoc -> SDoc
braces (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ CLabel -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable CLabel
ppr CLabel
lblSDoc -> SDoc -> SDoc
<>SDoc
colon
SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
hsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ ((GlobalReg, Maybe UnwindExpr) -> SDoc)
-> [(GlobalReg, Maybe UnwindExpr)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (GlobalReg, Maybe UnwindExpr) -> SDoc
forall {a} {a}. (Outputable a, Outputable a) => (a, a) -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Maybe a)
Instance of class: Outputable of the constraint type Outputable UnwindExpr
External instance of the constraint type Outputable GlobalReg
pprUw ([(GlobalReg, Maybe UnwindExpr)] -> [SDoc])
-> [(GlobalReg, Maybe UnwindExpr)] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ UnwindTable -> [(GlobalReg, Maybe UnwindExpr)]
forall k a. Map k a -> [(k, a)]
Map.toList UnwindTable
uws)
where
pprUw :: (a, a) -> SDoc
pprUw (a
g, a
expr) = a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
g SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'=' SDoc -> SDoc -> SDoc
<> a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
expr
type UnwindTable = Map.Map GlobalReg (Maybe UnwindExpr)
data UnwindExpr = UwConst !Int
| UwReg !GlobalReg !Int
| UwDeref UnwindExpr
| UwLabel CLabel
| UwPlus UnwindExpr UnwindExpr
| UwMinus UnwindExpr UnwindExpr
| UwTimes UnwindExpr UnwindExpr
deriving (UnwindExpr -> UnwindExpr -> Bool
(UnwindExpr -> UnwindExpr -> Bool)
-> (UnwindExpr -> UnwindExpr -> Bool) -> Eq UnwindExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnwindExpr -> UnwindExpr -> Bool
$c/= :: UnwindExpr -> UnwindExpr -> Bool
== :: UnwindExpr -> UnwindExpr -> Bool
$c== :: UnwindExpr -> UnwindExpr -> Bool
External instance of the constraint type Eq CLabel
Instance of class: Eq of the constraint type Eq UnwindExpr
External instance of the constraint type Eq GlobalReg
External instance of the constraint type Eq Int
External instance of the constraint type Eq Int
Instance of class: Eq of the constraint type Eq UnwindExpr
Eq)
instance Outputable UnwindExpr where
pprPrec :: Rational -> UnwindExpr -> SDoc
pprPrec Rational
_ (UwConst Int
i) = Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Int
ppr Int
i
pprPrec Rational
_ (UwReg GlobalReg
g Int
0) = GlobalReg -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable GlobalReg
ppr GlobalReg
g
pprPrec Rational
p (UwReg GlobalReg
g Int
x) = Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
p (UnwindExpr -> UnwindExpr -> UnwindExpr
UwPlus (GlobalReg -> Int -> UnwindExpr
UwReg GlobalReg
g Int
0) (Int -> UnwindExpr
UwConst Int
x))
pprPrec Rational
_ (UwDeref UnwindExpr
e) = Char -> SDoc
char Char
'*' SDoc -> SDoc -> SDoc
<> Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
3 UnwindExpr
e
pprPrec Rational
_ (UwLabel CLabel
l) = Rational -> CLabel -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
External instance of the constraint type Outputable CLabel
pprPrec Rational
3 CLabel
l
pprPrec Rational
p (UwPlus UnwindExpr
e0 UnwindExpr
e1) | Rational
p Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type forall a. Integral a => Ord (Ratio a)
External instance of the constraint type Integral Integer
<= Rational
0
= Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
0 UnwindExpr
e0 SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'+' SDoc -> SDoc -> SDoc
<> Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
0 UnwindExpr
e1
pprPrec Rational
p (UwMinus UnwindExpr
e0 UnwindExpr
e1) | Rational
p Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type forall a. Integral a => Ord (Ratio a)
External instance of the constraint type Integral Integer
<= Rational
0
= Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
1 UnwindExpr
e0 SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'-' SDoc -> SDoc -> SDoc
<> Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
1 UnwindExpr
e1
pprPrec Rational
p (UwTimes UnwindExpr
e0 UnwindExpr
e1) | Rational
p Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type forall a. Integral a => Ord (Ratio a)
External instance of the constraint type Integral Integer
<= Rational
1
= Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
2 UnwindExpr
e0 SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'*' SDoc -> SDoc -> SDoc
<> Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
2 UnwindExpr
e1
pprPrec Rational
_ UnwindExpr
other = SDoc -> SDoc
parens (Rational -> UnwindExpr -> SDoc
forall a. Outputable a => Rational -> a -> SDoc
Instance of class: Outputable of the constraint type Outputable UnwindExpr
pprPrec Rational
0 UnwindExpr
other)
toUnwindExpr :: Platform -> CmmExpr -> UnwindExpr
toUnwindExpr :: Platform -> CmmExpr -> UnwindExpr
toUnwindExpr Platform
_ (CmmLit (CmmInt Integer
i Width
_)) = Int -> UnwindExpr
UwConst (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Integer
fromIntegral Integer
i)
toUnwindExpr Platform
_ (CmmLit (CmmLabel CLabel
l)) = CLabel -> UnwindExpr
UwLabel CLabel
l
toUnwindExpr Platform
_ (CmmRegOff (CmmGlobal GlobalReg
g) Int
i) = GlobalReg -> Int -> UnwindExpr
UwReg GlobalReg
g Int
i
toUnwindExpr Platform
_ (CmmReg (CmmGlobal GlobalReg
g)) = GlobalReg -> Int -> UnwindExpr
UwReg GlobalReg
g Int
0
toUnwindExpr Platform
platform (CmmLoad CmmExpr
e CmmType
_) = UnwindExpr -> UnwindExpr
UwDeref (Platform -> CmmExpr -> UnwindExpr
toUnwindExpr Platform
platform CmmExpr
e)
toUnwindExpr Platform
platform e :: CmmExpr
e@(CmmMachOp MachOp
op [CmmExpr
e1, CmmExpr
e2]) =
case (MachOp
op, Platform -> CmmExpr -> UnwindExpr
toUnwindExpr Platform
platform CmmExpr
e1, Platform -> CmmExpr -> UnwindExpr
toUnwindExpr Platform
platform CmmExpr
e2) of
(MO_Add{}, UwReg GlobalReg
r Int
x, UwConst Int
y) -> GlobalReg -> Int -> UnwindExpr
UwReg GlobalReg
r (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
y)
(MO_Sub{}, UwReg GlobalReg
r Int
x, UwConst Int
y) -> GlobalReg -> Int -> UnwindExpr
UwReg GlobalReg
r (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
y)
(MO_Add{}, UwConst Int
x, UwReg GlobalReg
r Int
y) -> GlobalReg -> Int -> UnwindExpr
UwReg GlobalReg
r (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
y)
(MO_Add{}, UwConst Int
x, UwConst Int
y) -> Int -> UnwindExpr
UwConst (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
y)
(MO_Sub{}, UwConst Int
x, UwConst Int
y) -> Int -> UnwindExpr
UwConst (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
y)
(MO_Mul{}, UwConst Int
x, UwConst Int
y) -> Int -> UnwindExpr
UwConst (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
* Int
y)
(MO_Add{}, UnwindExpr
u1, UnwindExpr
u2 ) -> UnwindExpr -> UnwindExpr -> UnwindExpr
UwPlus UnwindExpr
u1 UnwindExpr
u2
(MO_Sub{}, UnwindExpr
u1, UnwindExpr
u2 ) -> UnwindExpr -> UnwindExpr -> UnwindExpr
UwMinus UnwindExpr
u1 UnwindExpr
u2
(MO_Mul{}, UnwindExpr
u1, UnwindExpr
u2 ) -> UnwindExpr -> UnwindExpr -> UnwindExpr
UwTimes UnwindExpr
u1 UnwindExpr
u2
(MachOp, UnwindExpr, UnwindExpr)
_otherwise -> String -> SDoc -> UnwindExpr
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Unsupported operator in unwind expression!"
(Platform -> CmmExpr -> SDoc
pprExpr Platform
platform CmmExpr
e)
toUnwindExpr Platform
_ CmmExpr
e
= String -> SDoc -> UnwindExpr
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Unsupported unwind expression!" (CmmExpr -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable CmmExpr
ppr CmmExpr
e)