{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# OPTIONS_GHC -fno-prof-late #-}
{-# LANGUAGE NamedFieldPuns #-}
module GHC.Internal.Heap.Closures (
Closure
, GenClosure(..)
, getClosureInfoTbl
, getClosureInfoTbl_maybe
, getClosurePtrArgs
, getClosurePtrArgs_maybe
, PrimType(..)
, WhatNext(..)
, WhyBlocked(..)
, TsoFlags(..)
, allClosures
, closureSize
, StgStackClosure
, GenStgStackClosure(..)
, StackFrame
, GenStackFrame(..)
, StackField
, GenStackField(..)
, Box(..)
, areBoxesEqual
, asBox
) where
import GHC.Internal.Base
import GHC.Internal.Show
import GHC.Internal.Heap.Constants
#if defined(PROFILING)
import GHC.Internal.Heap.InfoTable ()
import GHC.Internal.Heap.InfoTableProf
#else
import GHC.Internal.Heap.InfoTable
import GHC.Internal.Heap.InfoTableProf ()
#endif
import GHC.Internal.Heap.ProfInfo.Types
import GHC.Internal.Data.Bits
import GHC.Internal.Data.Foldable (Foldable, toList)
import GHC.Internal.Data.Traversable (Traversable)
import GHC.Internal.Int
import GHC.Internal.Num
import GHC.Internal.Real
import GHC.Internal.Word
import GHC.Internal.Exts
import GHC.Internal.Generics
import GHC.Internal.Numeric
import GHC.Internal.Stack (HasCallStack)
foreign import prim "aToWordzh" aToWord# :: Any -> Word#
foreign import prim "reallyUnsafePtrEqualityUpToTag"
reallyUnsafePtrEqualityUpToTag# :: Any -> Any -> Int#
data Box = Box Any
instance Show Box where
showsPrec :: Int -> Box -> ShowS
showsPrec Int
_ (Box Any
a) String
rs =
ShowS
pad_out (Word -> ShowS
forall a. Integral a => a -> ShowS
showHex Word
addr String
"") String -> ShowS
forall a. [a] -> [a] -> [a]
++ (if Word
tagWord -> Word -> Bool
forall a. Ord a => a -> a -> Bool
>Word
0 then String
"/" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word -> String
forall a. Show a => a -> String
show Word
tag else String
"") String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
rs
where
ptr :: Word
ptr = Word# -> Word
W# (Any -> Word#
aToWord# Any
a)
tag :: Word
tag = Word
ptr Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
tAG_MASK
addr :: Word
addr = Word
ptr Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
tag
pad_out :: ShowS
pad_out String
ls = Char
'0'Char -> ShowS
forall a. a -> [a] -> [a]
:Char
'x'Char -> ShowS
forall a. a -> [a] -> [a]
:String
ls
asBox :: a -> Box
asBox :: forall a. a -> Box
asBox a
x = Any -> Box
Box (a -> Any
forall a b. a -> b
unsafeCoerce# a
x)
areBoxesEqual :: Box -> Box -> IO Bool
areBoxesEqual :: Box -> Box -> IO Bool
areBoxesEqual (Box Any
a) (Box Any
b) = case Any -> Any -> Int#
reallyUnsafePtrEqualityUpToTag# Any
a Any
b of
Int#
0# -> Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
Int#
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
type Closure = GenClosure Box
data GenClosure b
=
ConstrClosure
{ forall b. GenClosure b -> StgInfoTable
info :: !StgInfoTable
, forall b. GenClosure b -> [b]
ptrArgs :: ![b]
, forall b. GenClosure b -> [Word]
dataArgs :: ![Word]
, forall b. GenClosure b -> String
pkg :: !String
, forall b. GenClosure b -> String
modl :: !String
, forall b. GenClosure b -> String
name :: !String
}
| FunClosure
{ info :: !StgInfoTable
, ptrArgs :: ![b]
, dataArgs :: ![Word]
}
| ThunkClosure
{ info :: !StgInfoTable
, ptrArgs :: ![b]
, dataArgs :: ![Word]
}
| SelectorClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> b
selectee :: !b
}
| PAPClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> HalfWord
arity :: !HalfWord
, forall b. GenClosure b -> HalfWord
n_args :: !HalfWord
, forall b. GenClosure b -> b
fun :: !b
, forall b. GenClosure b -> [b]
payload :: ![b]
}
| APClosure
{ info :: !StgInfoTable
, arity :: !HalfWord
, n_args :: !HalfWord
, fun :: !b
, payload :: ![b]
}
| APStackClosure
{ info :: !StgInfoTable
, fun :: !b
, payload :: ![b]
}
| IndClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> b
indirectee :: !b
}
| BCOClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> b
instrs :: !b
, forall b. GenClosure b -> b
literals :: !b
, forall b. GenClosure b -> b
bcoptrs :: !b
, arity :: !HalfWord
, forall b. GenClosure b -> HalfWord
size :: !HalfWord
, forall b. GenClosure b -> [Word]
bitmap :: ![Word]
}
| BlackholeClosure
{ info :: !StgInfoTable
, indirectee :: !b
}
| ArrWordsClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> Word
bytes :: !Word
, forall b. GenClosure b -> [Word]
arrWords :: ![Word]
}
| MutArrClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> Word
mccPtrs :: !Word
, forall b. GenClosure b -> Word
mccSize :: !Word
, forall b. GenClosure b -> [b]
mccPayload :: ![b]
}
| SmallMutArrClosure
{ info :: !StgInfoTable
, mccPtrs :: !Word
, mccPayload :: ![b]
}
| MVarClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> b
queueHead :: !b
, forall b. GenClosure b -> b
queueTail :: !b
, forall b. GenClosure b -> b
value :: !b
}
| MutVarClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> b
var :: !b
}
| BlockingQueueClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> b
link :: !b
, forall b. GenClosure b -> b
blackHole :: !b
, forall b. GenClosure b -> b
owner :: !b
, forall b. GenClosure b -> b
queue :: !b
}
| WeakClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> b
cfinalizers :: !b
, forall b. GenClosure b -> b
key :: !b
, value :: !b
, forall b. GenClosure b -> b
finalizer :: !b
, forall b. GenClosure b -> Maybe b
weakLink :: !(Maybe b)
}
| TSOClosure
{ info :: !StgInfoTable
, link :: !b
, forall b. GenClosure b -> b
global_link :: !b
, forall b. GenClosure b -> b
tsoStack :: !b
, forall b. GenClosure b -> b
trec :: !b
, forall b. GenClosure b -> b
blocked_exceptions :: !b
, forall b. GenClosure b -> b
bq :: !b
, forall b. GenClosure b -> Maybe b
thread_label :: !(Maybe b)
, forall b. GenClosure b -> WhatNext
what_next :: !WhatNext
, forall b. GenClosure b -> WhyBlocked
why_blocked :: !WhyBlocked
, forall b. GenClosure b -> [TsoFlags]
flags :: ![TsoFlags]
, forall b. GenClosure b -> Word64
threadId :: !Word64
, forall b. GenClosure b -> Word32
saved_errno :: !Word32
, forall b. GenClosure b -> Word32
tso_dirty :: !Word32
, forall b. GenClosure b -> Int64
alloc_limit :: !Int64
, forall b. GenClosure b -> Word32
tot_stack_size :: !Word32
, forall b. GenClosure b -> Maybe StgTSOProfInfo
prof :: !(Maybe StgTSOProfInfo)
}
| StackClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> Word32
stack_size :: !Word32
, forall b. GenClosure b -> Word8
stack_dirty :: !Word8
, forall b. GenClosure b -> Word8
stack_marking :: !Word8
}
| IntClosure
{ forall b. GenClosure b -> PrimType
ptipe :: PrimType
, forall b. GenClosure b -> Int
intVal :: !Int }
| WordClosure
{ ptipe :: PrimType
, forall b. GenClosure b -> Word
wordVal :: !Word }
| Int64Closure
{ ptipe :: PrimType
, forall b. GenClosure b -> Int64
int64Val :: !Int64 }
| Word64Closure
{ ptipe :: PrimType
, forall b. GenClosure b -> Word64
word64Val :: !Word64 }
| AddrClosure
{ ptipe :: PrimType
, forall b. GenClosure b -> Ptr ()
addrVal :: !(Ptr ()) }
| FloatClosure
{ ptipe :: PrimType
, forall b. GenClosure b -> Float
floatVal :: !Float }
| DoubleClosure
{ ptipe :: PrimType
, forall b. GenClosure b -> Double
doubleVal :: !Double }
| OtherClosure
{ info :: !StgInfoTable
, forall b. GenClosure b -> [b]
hvalues :: ![b]
, forall b. GenClosure b -> [Word]
rawWords :: ![Word]
}
| UnsupportedClosure
{ info :: !StgInfoTable
}
| UnknownTypeWordSizedPrimitive
{ wordVal :: !Word }
deriving (Int -> GenClosure b -> ShowS
[GenClosure b] -> ShowS
GenClosure b -> String
(Int -> GenClosure b -> ShowS)
-> (GenClosure b -> String)
-> ([GenClosure b] -> ShowS)
-> Show (GenClosure b)
forall b. Show b => Int -> GenClosure b -> ShowS
forall b. Show b => [GenClosure b] -> ShowS
forall b. Show b => GenClosure b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall b. Show b => Int -> GenClosure b -> ShowS
showsPrec :: Int -> GenClosure b -> ShowS
$cshow :: forall b. Show b => GenClosure b -> String
show :: GenClosure b -> String
$cshowList :: forall b. Show b => [GenClosure b] -> ShowS
showList :: [GenClosure b] -> ShowS
Show, (forall x. GenClosure b -> Rep (GenClosure b) x)
-> (forall x. Rep (GenClosure b) x -> GenClosure b)
-> Generic (GenClosure b)
forall x. Rep (GenClosure b) x -> GenClosure b
forall x. GenClosure b -> Rep (GenClosure b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (GenClosure b) x -> GenClosure b
forall b x. GenClosure b -> Rep (GenClosure b) x
$cfrom :: forall b x. GenClosure b -> Rep (GenClosure b) x
from :: forall x. GenClosure b -> Rep (GenClosure b) x
$cto :: forall b x. Rep (GenClosure b) x -> GenClosure b
to :: forall x. Rep (GenClosure b) x -> GenClosure b
Generic, (forall a b. (a -> b) -> GenClosure a -> GenClosure b)
-> (forall a b. a -> GenClosure b -> GenClosure a)
-> Functor GenClosure
forall a b. a -> GenClosure b -> GenClosure a
forall a b. (a -> b) -> GenClosure a -> GenClosure b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> GenClosure a -> GenClosure b
fmap :: forall a b. (a -> b) -> GenClosure a -> GenClosure b
$c<$ :: forall a b. a -> GenClosure b -> GenClosure a
<$ :: forall a b. a -> GenClosure b -> GenClosure a
Functor, (forall m. Monoid m => GenClosure m -> m)
-> (forall m a. Monoid m => (a -> m) -> GenClosure a -> m)
-> (forall m a. Monoid m => (a -> m) -> GenClosure a -> m)
-> (forall a b. (a -> b -> b) -> b -> GenClosure a -> b)
-> (forall a b. (a -> b -> b) -> b -> GenClosure a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenClosure a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenClosure a -> b)
-> (forall a. (a -> a -> a) -> GenClosure a -> a)
-> (forall a. (a -> a -> a) -> GenClosure a -> a)
-> (forall b. GenClosure b -> [b])
-> (forall a. GenClosure a -> Bool)
-> (forall b. GenClosure b -> Int)
-> (forall a. Eq a => a -> GenClosure a -> Bool)
-> (forall a. Ord a => GenClosure a -> a)
-> (forall a. Ord a => GenClosure a -> a)
-> (forall a. Num a => GenClosure a -> a)
-> (forall a. Num a => GenClosure a -> a)
-> Foldable GenClosure
forall a. Eq a => a -> GenClosure a -> Bool
forall a. Num a => GenClosure a -> a
forall a. Ord a => GenClosure a -> a
forall m. Monoid m => GenClosure m -> m
forall a. GenClosure a -> Bool
forall b. GenClosure b -> Int
forall b. GenClosure b -> [b]
forall a. (a -> a -> a) -> GenClosure a -> a
forall m a. Monoid m => (a -> m) -> GenClosure a -> m
forall b a. (b -> a -> b) -> b -> GenClosure a -> b
forall a b. (a -> b -> b) -> b -> GenClosure a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => GenClosure m -> m
fold :: forall m. Monoid m => GenClosure m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> GenClosure a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> GenClosure a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> GenClosure a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> GenClosure a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> GenClosure a -> b
foldr :: forall a b. (a -> b -> b) -> b -> GenClosure a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> GenClosure a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> GenClosure a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> GenClosure a -> b
foldl :: forall b a. (b -> a -> b) -> b -> GenClosure a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> GenClosure a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> GenClosure a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> GenClosure a -> a
foldr1 :: forall a. (a -> a -> a) -> GenClosure a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> GenClosure a -> a
foldl1 :: forall a. (a -> a -> a) -> GenClosure a -> a
$ctoList :: forall b. GenClosure b -> [b]
toList :: forall b. GenClosure b -> [b]
$cnull :: forall a. GenClosure a -> Bool
null :: forall a. GenClosure a -> Bool
$clength :: forall b. GenClosure b -> Int
length :: forall b. GenClosure b -> Int
$celem :: forall a. Eq a => a -> GenClosure a -> Bool
elem :: forall a. Eq a => a -> GenClosure a -> Bool
$cmaximum :: forall a. Ord a => GenClosure a -> a
maximum :: forall a. Ord a => GenClosure a -> a
$cminimum :: forall a. Ord a => GenClosure a -> a
minimum :: forall a. Ord a => GenClosure a -> a
$csum :: forall a. Num a => GenClosure a -> a
sum :: forall a. Num a => GenClosure a -> a
$cproduct :: forall a. Num a => GenClosure a -> a
product :: forall a. Num a => GenClosure a -> a
Foldable, Functor GenClosure
Foldable GenClosure
(Functor GenClosure, Foldable GenClosure) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenClosure a -> f (GenClosure b))
-> (forall (f :: * -> *) a.
Applicative f =>
GenClosure (f a) -> f (GenClosure a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenClosure a -> m (GenClosure b))
-> (forall (m :: * -> *) a.
Monad m =>
GenClosure (m a) -> m (GenClosure a))
-> Traversable GenClosure
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GenClosure (m a) -> m (GenClosure a)
forall (f :: * -> *) a.
Applicative f =>
GenClosure (f a) -> f (GenClosure a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenClosure a -> m (GenClosure b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenClosure a -> f (GenClosure b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenClosure a -> f (GenClosure b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenClosure a -> f (GenClosure b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenClosure (f a) -> f (GenClosure a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenClosure (f a) -> f (GenClosure a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenClosure a -> m (GenClosure b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenClosure a -> m (GenClosure b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
GenClosure (m a) -> m (GenClosure a)
sequence :: forall (m :: * -> *) a.
Monad m =>
GenClosure (m a) -> m (GenClosure a)
Traversable)
getClosureInfoTbl_maybe :: GenClosure b -> Maybe StgInfoTable
{-# INLINE getClosureInfoTbl_maybe #-}
getClosureInfoTbl_maybe :: forall b. GenClosure b -> Maybe StgInfoTable
getClosureInfoTbl_maybe GenClosure b
closure = case GenClosure b
closure of
ConstrClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
FunClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
ThunkClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
SelectorClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
PAPClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
APClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
APStackClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
IndClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
BCOClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
BlackholeClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
ArrWordsClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
MutArrClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
SmallMutArrClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
MVarClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
MutVarClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
BlockingQueueClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
WeakClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
TSOClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
StackClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} ->StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
IntClosure{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
WordClosure{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
Int64Closure{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
Word64Closure{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
AddrClosure{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
FloatClosure{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
DoubleClosure{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
OtherClosure{StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} -> StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
UnsupportedClosure {StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
info :: StgInfoTable
info} -> StgInfoTable -> Maybe StgInfoTable
forall a. a -> Maybe a
Just StgInfoTable
info
UnknownTypeWordSizedPrimitive{} -> Maybe StgInfoTable
forall a. Maybe a
Nothing
getClosureInfoTbl :: HasCallStack => GenClosure b -> StgInfoTable
getClosureInfoTbl :: forall b. HasCallStack => GenClosure b -> StgInfoTable
getClosureInfoTbl GenClosure b
closure = case GenClosure b -> Maybe StgInfoTable
forall b. GenClosure b -> Maybe StgInfoTable
getClosureInfoTbl_maybe GenClosure b
closure of
Just StgInfoTable
info -> StgInfoTable
info
Maybe StgInfoTable
Nothing -> String -> StgInfoTable
forall a. HasCallStack => String -> a
error String
"getClosureInfoTbl - Closure without info table"
getClosurePtrArgs_maybe :: GenClosure b -> Maybe [b]
{-# INLINE getClosurePtrArgs_maybe #-}
getClosurePtrArgs_maybe :: forall b. GenClosure b -> Maybe [b]
getClosurePtrArgs_maybe GenClosure b
closure = case GenClosure b
closure of
ConstrClosure{[b]
ptrArgs :: forall b. GenClosure b -> [b]
ptrArgs :: [b]
ptrArgs} -> [b] -> Maybe [b]
forall a. a -> Maybe a
Just [b]
ptrArgs
FunClosure{[b]
ptrArgs :: forall b. GenClosure b -> [b]
ptrArgs :: [b]
ptrArgs} -> [b] -> Maybe [b]
forall a. a -> Maybe a
Just [b]
ptrArgs
ThunkClosure{[b]
ptrArgs :: forall b. GenClosure b -> [b]
ptrArgs :: [b]
ptrArgs} -> [b] -> Maybe [b]
forall a. a -> Maybe a
Just [b]
ptrArgs
SelectorClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
PAPClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
APClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
APStackClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
IndClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
BCOClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
BlackholeClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
ArrWordsClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
MutArrClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
SmallMutArrClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
MVarClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
MutVarClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
BlockingQueueClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
WeakClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
TSOClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
StackClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
IntClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
WordClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
Int64Closure{} -> Maybe [b]
forall a. Maybe a
Nothing
Word64Closure{} -> Maybe [b]
forall a. Maybe a
Nothing
AddrClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
FloatClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
DoubleClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
OtherClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
UnsupportedClosure{} -> Maybe [b]
forall a. Maybe a
Nothing
UnknownTypeWordSizedPrimitive{} -> Maybe [b]
forall a. Maybe a
Nothing
getClosurePtrArgs :: HasCallStack => GenClosure b -> [b]
getClosurePtrArgs :: forall b. HasCallStack => GenClosure b -> [b]
getClosurePtrArgs GenClosure b
closure = case GenClosure b -> Maybe [b]
forall b. GenClosure b -> Maybe [b]
getClosurePtrArgs_maybe GenClosure b
closure of
Just [b]
ptrs -> [b]
ptrs
Maybe [b]
Nothing -> String -> [b]
forall a. HasCallStack => String -> a
error String
"getClosurePtrArgs - Closure without ptrArgs field"
type StgStackClosure = GenStgStackClosure Box
data GenStgStackClosure b = GenStgStackClosure
{ forall b. GenStgStackClosure b -> StgInfoTable
ssc_info :: !StgInfoTable
, forall b. GenStgStackClosure b -> Word32
ssc_stack_size :: !Word32
, forall b. GenStgStackClosure b -> [GenStackFrame b]
ssc_stack :: ![GenStackFrame b]
}
deriving ((forall m. Monoid m => GenStgStackClosure m -> m)
-> (forall m a. Monoid m => (a -> m) -> GenStgStackClosure a -> m)
-> (forall m a. Monoid m => (a -> m) -> GenStgStackClosure a -> m)
-> (forall a b. (a -> b -> b) -> b -> GenStgStackClosure a -> b)
-> (forall a b. (a -> b -> b) -> b -> GenStgStackClosure a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenStgStackClosure a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenStgStackClosure a -> b)
-> (forall a. (a -> a -> a) -> GenStgStackClosure a -> a)
-> (forall a. (a -> a -> a) -> GenStgStackClosure a -> a)
-> (forall a. GenStgStackClosure a -> [a])
-> (forall a. GenStgStackClosure a -> Bool)
-> (forall a. GenStgStackClosure a -> Int)
-> (forall a. Eq a => a -> GenStgStackClosure a -> Bool)
-> (forall a. Ord a => GenStgStackClosure a -> a)
-> (forall a. Ord a => GenStgStackClosure a -> a)
-> (forall a. Num a => GenStgStackClosure a -> a)
-> (forall a. Num a => GenStgStackClosure a -> a)
-> Foldable GenStgStackClosure
forall a. Eq a => a -> GenStgStackClosure a -> Bool
forall a. Num a => GenStgStackClosure a -> a
forall a. Ord a => GenStgStackClosure a -> a
forall m. Monoid m => GenStgStackClosure m -> m
forall a. GenStgStackClosure a -> Bool
forall a. GenStgStackClosure a -> Int
forall a. GenStgStackClosure a -> [a]
forall a. (a -> a -> a) -> GenStgStackClosure a -> a
forall m a. Monoid m => (a -> m) -> GenStgStackClosure a -> m
forall b a. (b -> a -> b) -> b -> GenStgStackClosure a -> b
forall a b. (a -> b -> b) -> b -> GenStgStackClosure a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => GenStgStackClosure m -> m
fold :: forall m. Monoid m => GenStgStackClosure m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> GenStgStackClosure a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> GenStgStackClosure a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> GenStgStackClosure a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> GenStgStackClosure a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> GenStgStackClosure a -> b
foldr :: forall a b. (a -> b -> b) -> b -> GenStgStackClosure a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> GenStgStackClosure a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> GenStgStackClosure a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> GenStgStackClosure a -> b
foldl :: forall b a. (b -> a -> b) -> b -> GenStgStackClosure a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> GenStgStackClosure a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> GenStgStackClosure a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> GenStgStackClosure a -> a
foldr1 :: forall a. (a -> a -> a) -> GenStgStackClosure a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> GenStgStackClosure a -> a
foldl1 :: forall a. (a -> a -> a) -> GenStgStackClosure a -> a
$ctoList :: forall a. GenStgStackClosure a -> [a]
toList :: forall a. GenStgStackClosure a -> [a]
$cnull :: forall a. GenStgStackClosure a -> Bool
null :: forall a. GenStgStackClosure a -> Bool
$clength :: forall a. GenStgStackClosure a -> Int
length :: forall a. GenStgStackClosure a -> Int
$celem :: forall a. Eq a => a -> GenStgStackClosure a -> Bool
elem :: forall a. Eq a => a -> GenStgStackClosure a -> Bool
$cmaximum :: forall a. Ord a => GenStgStackClosure a -> a
maximum :: forall a. Ord a => GenStgStackClosure a -> a
$cminimum :: forall a. Ord a => GenStgStackClosure a -> a
minimum :: forall a. Ord a => GenStgStackClosure a -> a
$csum :: forall a. Num a => GenStgStackClosure a -> a
sum :: forall a. Num a => GenStgStackClosure a -> a
$cproduct :: forall a. Num a => GenStgStackClosure a -> a
product :: forall a. Num a => GenStgStackClosure a -> a
Foldable, (forall a b.
(a -> b) -> GenStgStackClosure a -> GenStgStackClosure b)
-> (forall a b. a -> GenStgStackClosure b -> GenStgStackClosure a)
-> Functor GenStgStackClosure
forall a b. a -> GenStgStackClosure b -> GenStgStackClosure a
forall a b.
(a -> b) -> GenStgStackClosure a -> GenStgStackClosure b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> GenStgStackClosure a -> GenStgStackClosure b
fmap :: forall a b.
(a -> b) -> GenStgStackClosure a -> GenStgStackClosure b
$c<$ :: forall a b. a -> GenStgStackClosure b -> GenStgStackClosure a
<$ :: forall a b. a -> GenStgStackClosure b -> GenStgStackClosure a
Functor, (forall x. GenStgStackClosure b -> Rep (GenStgStackClosure b) x)
-> (forall x. Rep (GenStgStackClosure b) x -> GenStgStackClosure b)
-> Generic (GenStgStackClosure b)
forall x. Rep (GenStgStackClosure b) x -> GenStgStackClosure b
forall x. GenStgStackClosure b -> Rep (GenStgStackClosure b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (GenStgStackClosure b) x -> GenStgStackClosure b
forall b x. GenStgStackClosure b -> Rep (GenStgStackClosure b) x
$cfrom :: forall b x. GenStgStackClosure b -> Rep (GenStgStackClosure b) x
from :: forall x. GenStgStackClosure b -> Rep (GenStgStackClosure b) x
$cto :: forall b x. Rep (GenStgStackClosure b) x -> GenStgStackClosure b
to :: forall x. Rep (GenStgStackClosure b) x -> GenStgStackClosure b
Generic, Int -> GenStgStackClosure b -> ShowS
[GenStgStackClosure b] -> ShowS
GenStgStackClosure b -> String
(Int -> GenStgStackClosure b -> ShowS)
-> (GenStgStackClosure b -> String)
-> ([GenStgStackClosure b] -> ShowS)
-> Show (GenStgStackClosure b)
forall b. Show b => Int -> GenStgStackClosure b -> ShowS
forall b. Show b => [GenStgStackClosure b] -> ShowS
forall b. Show b => GenStgStackClosure b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall b. Show b => Int -> GenStgStackClosure b -> ShowS
showsPrec :: Int -> GenStgStackClosure b -> ShowS
$cshow :: forall b. Show b => GenStgStackClosure b -> String
show :: GenStgStackClosure b -> String
$cshowList :: forall b. Show b => [GenStgStackClosure b] -> ShowS
showList :: [GenStgStackClosure b] -> ShowS
Show, Functor GenStgStackClosure
Foldable GenStgStackClosure
(Functor GenStgStackClosure, Foldable GenStgStackClosure) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStgStackClosure a -> f (GenStgStackClosure b))
-> (forall (f :: * -> *) a.
Applicative f =>
GenStgStackClosure (f a) -> f (GenStgStackClosure a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStgStackClosure a -> m (GenStgStackClosure b))
-> (forall (m :: * -> *) a.
Monad m =>
GenStgStackClosure (m a) -> m (GenStgStackClosure a))
-> Traversable GenStgStackClosure
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GenStgStackClosure (m a) -> m (GenStgStackClosure a)
forall (f :: * -> *) a.
Applicative f =>
GenStgStackClosure (f a) -> f (GenStgStackClosure a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStgStackClosure a -> m (GenStgStackClosure b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStgStackClosure a -> f (GenStgStackClosure b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStgStackClosure a -> f (GenStgStackClosure b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStgStackClosure a -> f (GenStgStackClosure b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenStgStackClosure (f a) -> f (GenStgStackClosure a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenStgStackClosure (f a) -> f (GenStgStackClosure a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStgStackClosure a -> m (GenStgStackClosure b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStgStackClosure a -> m (GenStgStackClosure b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
GenStgStackClosure (m a) -> m (GenStgStackClosure a)
sequence :: forall (m :: * -> *) a.
Monad m =>
GenStgStackClosure (m a) -> m (GenStgStackClosure a)
Traversable)
type StackField = GenStackField Box
data GenStackField b
= StackWord !Word
| StackBox !b
deriving ((forall m. Monoid m => GenStackField m -> m)
-> (forall m a. Monoid m => (a -> m) -> GenStackField a -> m)
-> (forall m a. Monoid m => (a -> m) -> GenStackField a -> m)
-> (forall a b. (a -> b -> b) -> b -> GenStackField a -> b)
-> (forall a b. (a -> b -> b) -> b -> GenStackField a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenStackField a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenStackField a -> b)
-> (forall a. (a -> a -> a) -> GenStackField a -> a)
-> (forall a. (a -> a -> a) -> GenStackField a -> a)
-> (forall a. GenStackField a -> [a])
-> (forall a. GenStackField a -> Bool)
-> (forall a. GenStackField a -> Int)
-> (forall a. Eq a => a -> GenStackField a -> Bool)
-> (forall a. Ord a => GenStackField a -> a)
-> (forall a. Ord a => GenStackField a -> a)
-> (forall a. Num a => GenStackField a -> a)
-> (forall a. Num a => GenStackField a -> a)
-> Foldable GenStackField
forall a. Eq a => a -> GenStackField a -> Bool
forall a. Num a => GenStackField a -> a
forall a. Ord a => GenStackField a -> a
forall m. Monoid m => GenStackField m -> m
forall a. GenStackField a -> Bool
forall a. GenStackField a -> Int
forall a. GenStackField a -> [a]
forall a. (a -> a -> a) -> GenStackField a -> a
forall m a. Monoid m => (a -> m) -> GenStackField a -> m
forall b a. (b -> a -> b) -> b -> GenStackField a -> b
forall a b. (a -> b -> b) -> b -> GenStackField a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => GenStackField m -> m
fold :: forall m. Monoid m => GenStackField m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> GenStackField a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> GenStackField a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> GenStackField a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> GenStackField a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> GenStackField a -> b
foldr :: forall a b. (a -> b -> b) -> b -> GenStackField a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> GenStackField a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> GenStackField a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> GenStackField a -> b
foldl :: forall b a. (b -> a -> b) -> b -> GenStackField a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> GenStackField a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> GenStackField a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> GenStackField a -> a
foldr1 :: forall a. (a -> a -> a) -> GenStackField a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> GenStackField a -> a
foldl1 :: forall a. (a -> a -> a) -> GenStackField a -> a
$ctoList :: forall a. GenStackField a -> [a]
toList :: forall a. GenStackField a -> [a]
$cnull :: forall a. GenStackField a -> Bool
null :: forall a. GenStackField a -> Bool
$clength :: forall a. GenStackField a -> Int
length :: forall a. GenStackField a -> Int
$celem :: forall a. Eq a => a -> GenStackField a -> Bool
elem :: forall a. Eq a => a -> GenStackField a -> Bool
$cmaximum :: forall a. Ord a => GenStackField a -> a
maximum :: forall a. Ord a => GenStackField a -> a
$cminimum :: forall a. Ord a => GenStackField a -> a
minimum :: forall a. Ord a => GenStackField a -> a
$csum :: forall a. Num a => GenStackField a -> a
sum :: forall a. Num a => GenStackField a -> a
$cproduct :: forall a. Num a => GenStackField a -> a
product :: forall a. Num a => GenStackField a -> a
Foldable, (forall a b. (a -> b) -> GenStackField a -> GenStackField b)
-> (forall a b. a -> GenStackField b -> GenStackField a)
-> Functor GenStackField
forall a b. a -> GenStackField b -> GenStackField a
forall a b. (a -> b) -> GenStackField a -> GenStackField b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> GenStackField a -> GenStackField b
fmap :: forall a b. (a -> b) -> GenStackField a -> GenStackField b
$c<$ :: forall a b. a -> GenStackField b -> GenStackField a
<$ :: forall a b. a -> GenStackField b -> GenStackField a
Functor, (forall x. GenStackField b -> Rep (GenStackField b) x)
-> (forall x. Rep (GenStackField b) x -> GenStackField b)
-> Generic (GenStackField b)
forall x. Rep (GenStackField b) x -> GenStackField b
forall x. GenStackField b -> Rep (GenStackField b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (GenStackField b) x -> GenStackField b
forall b x. GenStackField b -> Rep (GenStackField b) x
$cfrom :: forall b x. GenStackField b -> Rep (GenStackField b) x
from :: forall x. GenStackField b -> Rep (GenStackField b) x
$cto :: forall b x. Rep (GenStackField b) x -> GenStackField b
to :: forall x. Rep (GenStackField b) x -> GenStackField b
Generic, Int -> GenStackField b -> ShowS
[GenStackField b] -> ShowS
GenStackField b -> String
(Int -> GenStackField b -> ShowS)
-> (GenStackField b -> String)
-> ([GenStackField b] -> ShowS)
-> Show (GenStackField b)
forall b. Show b => Int -> GenStackField b -> ShowS
forall b. Show b => [GenStackField b] -> ShowS
forall b. Show b => GenStackField b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall b. Show b => Int -> GenStackField b -> ShowS
showsPrec :: Int -> GenStackField b -> ShowS
$cshow :: forall b. Show b => GenStackField b -> String
show :: GenStackField b -> String
$cshowList :: forall b. Show b => [GenStackField b] -> ShowS
showList :: [GenStackField b] -> ShowS
Show, Functor GenStackField
Foldable GenStackField
(Functor GenStackField, Foldable GenStackField) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackField a -> f (GenStackField b))
-> (forall (f :: * -> *) a.
Applicative f =>
GenStackField (f a) -> f (GenStackField a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackField a -> m (GenStackField b))
-> (forall (m :: * -> *) a.
Monad m =>
GenStackField (m a) -> m (GenStackField a))
-> Traversable GenStackField
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GenStackField (m a) -> m (GenStackField a)
forall (f :: * -> *) a.
Applicative f =>
GenStackField (f a) -> f (GenStackField a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackField a -> m (GenStackField b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackField a -> f (GenStackField b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackField a -> f (GenStackField b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackField a -> f (GenStackField b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenStackField (f a) -> f (GenStackField a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenStackField (f a) -> f (GenStackField a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackField a -> m (GenStackField b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackField a -> m (GenStackField b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
GenStackField (m a) -> m (GenStackField a)
sequence :: forall (m :: * -> *) a.
Monad m =>
GenStackField (m a) -> m (GenStackField a)
Traversable)
type StackFrame = GenStackFrame Box
data GenStackFrame b =
UpdateFrame
{ forall b. GenStackFrame b -> StgInfoTable
info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> b
updatee :: !b
}
| CatchFrame
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> b
handler :: !b
}
| CatchStmFrame
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> b
catchFrameCode :: !b
, handler :: !b
}
| CatchRetryFrame
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> Word
running_alt_code :: !Word
, forall b. GenStackFrame b -> b
first_code :: !b
, forall b. GenStackFrame b -> b
alt_code :: !b
}
| AtomicallyFrame
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> b
atomicallyFrameCode :: !b
, forall b. GenStackFrame b -> b
result :: !b
}
| UnderflowFrame
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> GenStgStackClosure b
nextChunk :: !(GenStgStackClosure b)
}
| StopFrame
{ info_tbl :: !StgInfoTable }
| RetSmall
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> [GenStackField b]
stack_payload :: ![GenStackField b]
}
| RetBig
{ info_tbl :: !StgInfoTable
, stack_payload :: ![GenStackField b]
}
| RetFun
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> Word
retFunSize :: !Word
, forall b. GenStackFrame b -> b
retFunFun :: !b
, forall b. GenStackFrame b -> [GenStackField b]
retFunPayload :: ![GenStackField b]
}
| RetBCO
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> b
bco :: !b
, forall b. GenStackFrame b -> [GenStackField b]
bcoArgs :: ![GenStackField b]
}
| AnnFrame
{ info_tbl :: !StgInfoTable
, forall b. GenStackFrame b -> b
annotation :: !b
}
deriving ((forall m. Monoid m => GenStackFrame m -> m)
-> (forall m a. Monoid m => (a -> m) -> GenStackFrame a -> m)
-> (forall m a. Monoid m => (a -> m) -> GenStackFrame a -> m)
-> (forall a b. (a -> b -> b) -> b -> GenStackFrame a -> b)
-> (forall a b. (a -> b -> b) -> b -> GenStackFrame a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenStackFrame a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenStackFrame a -> b)
-> (forall a. (a -> a -> a) -> GenStackFrame a -> a)
-> (forall a. (a -> a -> a) -> GenStackFrame a -> a)
-> (forall a. GenStackFrame a -> [a])
-> (forall a. GenStackFrame a -> Bool)
-> (forall a. GenStackFrame a -> Int)
-> (forall a. Eq a => a -> GenStackFrame a -> Bool)
-> (forall a. Ord a => GenStackFrame a -> a)
-> (forall a. Ord a => GenStackFrame a -> a)
-> (forall a. Num a => GenStackFrame a -> a)
-> (forall a. Num a => GenStackFrame a -> a)
-> Foldable GenStackFrame
forall a. Eq a => a -> GenStackFrame a -> Bool
forall a. Num a => GenStackFrame a -> a
forall a. Ord a => GenStackFrame a -> a
forall m. Monoid m => GenStackFrame m -> m
forall a. GenStackFrame a -> Bool
forall a. GenStackFrame a -> Int
forall a. GenStackFrame a -> [a]
forall a. (a -> a -> a) -> GenStackFrame a -> a
forall m a. Monoid m => (a -> m) -> GenStackFrame a -> m
forall b a. (b -> a -> b) -> b -> GenStackFrame a -> b
forall a b. (a -> b -> b) -> b -> GenStackFrame a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => GenStackFrame m -> m
fold :: forall m. Monoid m => GenStackFrame m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> GenStackFrame a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> GenStackFrame a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> GenStackFrame a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> GenStackFrame a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> GenStackFrame a -> b
foldr :: forall a b. (a -> b -> b) -> b -> GenStackFrame a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> GenStackFrame a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> GenStackFrame a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> GenStackFrame a -> b
foldl :: forall b a. (b -> a -> b) -> b -> GenStackFrame a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> GenStackFrame a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> GenStackFrame a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> GenStackFrame a -> a
foldr1 :: forall a. (a -> a -> a) -> GenStackFrame a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> GenStackFrame a -> a
foldl1 :: forall a. (a -> a -> a) -> GenStackFrame a -> a
$ctoList :: forall a. GenStackFrame a -> [a]
toList :: forall a. GenStackFrame a -> [a]
$cnull :: forall a. GenStackFrame a -> Bool
null :: forall a. GenStackFrame a -> Bool
$clength :: forall a. GenStackFrame a -> Int
length :: forall a. GenStackFrame a -> Int
$celem :: forall a. Eq a => a -> GenStackFrame a -> Bool
elem :: forall a. Eq a => a -> GenStackFrame a -> Bool
$cmaximum :: forall a. Ord a => GenStackFrame a -> a
maximum :: forall a. Ord a => GenStackFrame a -> a
$cminimum :: forall a. Ord a => GenStackFrame a -> a
minimum :: forall a. Ord a => GenStackFrame a -> a
$csum :: forall a. Num a => GenStackFrame a -> a
sum :: forall a. Num a => GenStackFrame a -> a
$cproduct :: forall a. Num a => GenStackFrame a -> a
product :: forall a. Num a => GenStackFrame a -> a
Foldable, (forall a b. (a -> b) -> GenStackFrame a -> GenStackFrame b)
-> (forall a b. a -> GenStackFrame b -> GenStackFrame a)
-> Functor GenStackFrame
forall a b. a -> GenStackFrame b -> GenStackFrame a
forall a b. (a -> b) -> GenStackFrame a -> GenStackFrame b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> GenStackFrame a -> GenStackFrame b
fmap :: forall a b. (a -> b) -> GenStackFrame a -> GenStackFrame b
$c<$ :: forall a b. a -> GenStackFrame b -> GenStackFrame a
<$ :: forall a b. a -> GenStackFrame b -> GenStackFrame a
Functor, (forall x. GenStackFrame b -> Rep (GenStackFrame b) x)
-> (forall x. Rep (GenStackFrame b) x -> GenStackFrame b)
-> Generic (GenStackFrame b)
forall x. Rep (GenStackFrame b) x -> GenStackFrame b
forall x. GenStackFrame b -> Rep (GenStackFrame b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (GenStackFrame b) x -> GenStackFrame b
forall b x. GenStackFrame b -> Rep (GenStackFrame b) x
$cfrom :: forall b x. GenStackFrame b -> Rep (GenStackFrame b) x
from :: forall x. GenStackFrame b -> Rep (GenStackFrame b) x
$cto :: forall b x. Rep (GenStackFrame b) x -> GenStackFrame b
to :: forall x. Rep (GenStackFrame b) x -> GenStackFrame b
Generic, Int -> GenStackFrame b -> ShowS
[GenStackFrame b] -> ShowS
GenStackFrame b -> String
(Int -> GenStackFrame b -> ShowS)
-> (GenStackFrame b -> String)
-> ([GenStackFrame b] -> ShowS)
-> Show (GenStackFrame b)
forall b. Show b => Int -> GenStackFrame b -> ShowS
forall b. Show b => [GenStackFrame b] -> ShowS
forall b. Show b => GenStackFrame b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall b. Show b => Int -> GenStackFrame b -> ShowS
showsPrec :: Int -> GenStackFrame b -> ShowS
$cshow :: forall b. Show b => GenStackFrame b -> String
show :: GenStackFrame b -> String
$cshowList :: forall b. Show b => [GenStackFrame b] -> ShowS
showList :: [GenStackFrame b] -> ShowS
Show, Functor GenStackFrame
Foldable GenStackFrame
(Functor GenStackFrame, Foldable GenStackFrame) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackFrame a -> f (GenStackFrame b))
-> (forall (f :: * -> *) a.
Applicative f =>
GenStackFrame (f a) -> f (GenStackFrame a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackFrame a -> m (GenStackFrame b))
-> (forall (m :: * -> *) a.
Monad m =>
GenStackFrame (m a) -> m (GenStackFrame a))
-> Traversable GenStackFrame
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GenStackFrame (m a) -> m (GenStackFrame a)
forall (f :: * -> *) a.
Applicative f =>
GenStackFrame (f a) -> f (GenStackFrame a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackFrame a -> m (GenStackFrame b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackFrame a -> f (GenStackFrame b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackFrame a -> f (GenStackFrame b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenStackFrame a -> f (GenStackFrame b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenStackFrame (f a) -> f (GenStackFrame a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenStackFrame (f a) -> f (GenStackFrame a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackFrame a -> m (GenStackFrame b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenStackFrame a -> m (GenStackFrame b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
GenStackFrame (m a) -> m (GenStackFrame a)
sequence :: forall (m :: * -> *) a.
Monad m =>
GenStackFrame (m a) -> m (GenStackFrame a)
Traversable)
data PrimType
= PInt
| PWord
| PInt64
| PWord64
| PAddr
| PFloat
| PDouble
deriving (PrimType -> PrimType -> Bool
(PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool) -> Eq PrimType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrimType -> PrimType -> Bool
== :: PrimType -> PrimType -> Bool
$c/= :: PrimType -> PrimType -> Bool
/= :: PrimType -> PrimType -> Bool
Eq, Int -> PrimType -> ShowS
[PrimType] -> ShowS
PrimType -> String
(Int -> PrimType -> ShowS)
-> (PrimType -> String) -> ([PrimType] -> ShowS) -> Show PrimType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimType -> ShowS
showsPrec :: Int -> PrimType -> ShowS
$cshow :: PrimType -> String
show :: PrimType -> String
$cshowList :: [PrimType] -> ShowS
showList :: [PrimType] -> ShowS
Show, (forall x. PrimType -> Rep PrimType x)
-> (forall x. Rep PrimType x -> PrimType) -> Generic PrimType
forall x. Rep PrimType x -> PrimType
forall x. PrimType -> Rep PrimType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PrimType -> Rep PrimType x
from :: forall x. PrimType -> Rep PrimType x
$cto :: forall x. Rep PrimType x -> PrimType
to :: forall x. Rep PrimType x -> PrimType
Generic, Eq PrimType
Eq PrimType =>
(PrimType -> PrimType -> Ordering)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> PrimType)
-> (PrimType -> PrimType -> PrimType)
-> Ord PrimType
PrimType -> PrimType -> Bool
PrimType -> PrimType -> Ordering
PrimType -> PrimType -> PrimType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PrimType -> PrimType -> Ordering
compare :: PrimType -> PrimType -> Ordering
$c< :: PrimType -> PrimType -> Bool
< :: PrimType -> PrimType -> Bool
$c<= :: PrimType -> PrimType -> Bool
<= :: PrimType -> PrimType -> Bool
$c> :: PrimType -> PrimType -> Bool
> :: PrimType -> PrimType -> Bool
$c>= :: PrimType -> PrimType -> Bool
>= :: PrimType -> PrimType -> Bool
$cmax :: PrimType -> PrimType -> PrimType
max :: PrimType -> PrimType -> PrimType
$cmin :: PrimType -> PrimType -> PrimType
min :: PrimType -> PrimType -> PrimType
Ord)
data WhatNext
= ThreadRunGHC
| ThreadInterpret
| ThreadKilled
| ThreadComplete
| WhatNextUnknownValue Word16
deriving (WhatNext -> WhatNext -> Bool
(WhatNext -> WhatNext -> Bool)
-> (WhatNext -> WhatNext -> Bool) -> Eq WhatNext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WhatNext -> WhatNext -> Bool
== :: WhatNext -> WhatNext -> Bool
$c/= :: WhatNext -> WhatNext -> Bool
/= :: WhatNext -> WhatNext -> Bool
Eq, Int -> WhatNext -> ShowS
[WhatNext] -> ShowS
WhatNext -> String
(Int -> WhatNext -> ShowS)
-> (WhatNext -> String) -> ([WhatNext] -> ShowS) -> Show WhatNext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WhatNext -> ShowS
showsPrec :: Int -> WhatNext -> ShowS
$cshow :: WhatNext -> String
show :: WhatNext -> String
$cshowList :: [WhatNext] -> ShowS
showList :: [WhatNext] -> ShowS
Show, (forall x. WhatNext -> Rep WhatNext x)
-> (forall x. Rep WhatNext x -> WhatNext) -> Generic WhatNext
forall x. Rep WhatNext x -> WhatNext
forall x. WhatNext -> Rep WhatNext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WhatNext -> Rep WhatNext x
from :: forall x. WhatNext -> Rep WhatNext x
$cto :: forall x. Rep WhatNext x -> WhatNext
to :: forall x. Rep WhatNext x -> WhatNext
Generic, Eq WhatNext
Eq WhatNext =>
(WhatNext -> WhatNext -> Ordering)
-> (WhatNext -> WhatNext -> Bool)
-> (WhatNext -> WhatNext -> Bool)
-> (WhatNext -> WhatNext -> Bool)
-> (WhatNext -> WhatNext -> Bool)
-> (WhatNext -> WhatNext -> WhatNext)
-> (WhatNext -> WhatNext -> WhatNext)
-> Ord WhatNext
WhatNext -> WhatNext -> Bool
WhatNext -> WhatNext -> Ordering
WhatNext -> WhatNext -> WhatNext
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WhatNext -> WhatNext -> Ordering
compare :: WhatNext -> WhatNext -> Ordering
$c< :: WhatNext -> WhatNext -> Bool
< :: WhatNext -> WhatNext -> Bool
$c<= :: WhatNext -> WhatNext -> Bool
<= :: WhatNext -> WhatNext -> Bool
$c> :: WhatNext -> WhatNext -> Bool
> :: WhatNext -> WhatNext -> Bool
$c>= :: WhatNext -> WhatNext -> Bool
>= :: WhatNext -> WhatNext -> Bool
$cmax :: WhatNext -> WhatNext -> WhatNext
max :: WhatNext -> WhatNext -> WhatNext
$cmin :: WhatNext -> WhatNext -> WhatNext
min :: WhatNext -> WhatNext -> WhatNext
Ord)
data WhyBlocked
= NotBlocked
| BlockedOnMVar
| BlockedOnMVarRead
| BlockedOnBlackHole
| BlockedOnRead
| BlockedOnWrite
| BlockedOnDelay
| BlockedOnSTM
| BlockedOnDoProc
| BlockedOnCCall
| BlockedOnCCall_Interruptible
| BlockedOnMsgThrowTo
| ThreadMigrating
| WhyBlockedUnknownValue Word16
deriving (WhyBlocked -> WhyBlocked -> Bool
(WhyBlocked -> WhyBlocked -> Bool)
-> (WhyBlocked -> WhyBlocked -> Bool) -> Eq WhyBlocked
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WhyBlocked -> WhyBlocked -> Bool
== :: WhyBlocked -> WhyBlocked -> Bool
$c/= :: WhyBlocked -> WhyBlocked -> Bool
/= :: WhyBlocked -> WhyBlocked -> Bool
Eq, Int -> WhyBlocked -> ShowS
[WhyBlocked] -> ShowS
WhyBlocked -> String
(Int -> WhyBlocked -> ShowS)
-> (WhyBlocked -> String)
-> ([WhyBlocked] -> ShowS)
-> Show WhyBlocked
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WhyBlocked -> ShowS
showsPrec :: Int -> WhyBlocked -> ShowS
$cshow :: WhyBlocked -> String
show :: WhyBlocked -> String
$cshowList :: [WhyBlocked] -> ShowS
showList :: [WhyBlocked] -> ShowS
Show, (forall x. WhyBlocked -> Rep WhyBlocked x)
-> (forall x. Rep WhyBlocked x -> WhyBlocked) -> Generic WhyBlocked
forall x. Rep WhyBlocked x -> WhyBlocked
forall x. WhyBlocked -> Rep WhyBlocked x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WhyBlocked -> Rep WhyBlocked x
from :: forall x. WhyBlocked -> Rep WhyBlocked x
$cto :: forall x. Rep WhyBlocked x -> WhyBlocked
to :: forall x. Rep WhyBlocked x -> WhyBlocked
Generic, Eq WhyBlocked
Eq WhyBlocked =>
(WhyBlocked -> WhyBlocked -> Ordering)
-> (WhyBlocked -> WhyBlocked -> Bool)
-> (WhyBlocked -> WhyBlocked -> Bool)
-> (WhyBlocked -> WhyBlocked -> Bool)
-> (WhyBlocked -> WhyBlocked -> Bool)
-> (WhyBlocked -> WhyBlocked -> WhyBlocked)
-> (WhyBlocked -> WhyBlocked -> WhyBlocked)
-> Ord WhyBlocked
WhyBlocked -> WhyBlocked -> Bool
WhyBlocked -> WhyBlocked -> Ordering
WhyBlocked -> WhyBlocked -> WhyBlocked
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WhyBlocked -> WhyBlocked -> Ordering
compare :: WhyBlocked -> WhyBlocked -> Ordering
$c< :: WhyBlocked -> WhyBlocked -> Bool
< :: WhyBlocked -> WhyBlocked -> Bool
$c<= :: WhyBlocked -> WhyBlocked -> Bool
<= :: WhyBlocked -> WhyBlocked -> Bool
$c> :: WhyBlocked -> WhyBlocked -> Bool
> :: WhyBlocked -> WhyBlocked -> Bool
$c>= :: WhyBlocked -> WhyBlocked -> Bool
>= :: WhyBlocked -> WhyBlocked -> Bool
$cmax :: WhyBlocked -> WhyBlocked -> WhyBlocked
max :: WhyBlocked -> WhyBlocked -> WhyBlocked
$cmin :: WhyBlocked -> WhyBlocked -> WhyBlocked
min :: WhyBlocked -> WhyBlocked -> WhyBlocked
Ord)
data TsoFlags
= TsoLocked
| TsoBlockx
| TsoInterruptible
| TsoStoppedOnBreakpoint
| TsoMarked
| TsoSqueezed
| TsoAllocLimit
| TsoStopNextBreakpoint
| TsoStopAfterReturn
| TsoFlagsUnknownValue Word32
deriving (TsoFlags -> TsoFlags -> Bool
(TsoFlags -> TsoFlags -> Bool)
-> (TsoFlags -> TsoFlags -> Bool) -> Eq TsoFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TsoFlags -> TsoFlags -> Bool
== :: TsoFlags -> TsoFlags -> Bool
$c/= :: TsoFlags -> TsoFlags -> Bool
/= :: TsoFlags -> TsoFlags -> Bool
Eq, Int -> TsoFlags -> ShowS
[TsoFlags] -> ShowS
TsoFlags -> String
(Int -> TsoFlags -> ShowS)
-> (TsoFlags -> String) -> ([TsoFlags] -> ShowS) -> Show TsoFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TsoFlags -> ShowS
showsPrec :: Int -> TsoFlags -> ShowS
$cshow :: TsoFlags -> String
show :: TsoFlags -> String
$cshowList :: [TsoFlags] -> ShowS
showList :: [TsoFlags] -> ShowS
Show, (forall x. TsoFlags -> Rep TsoFlags x)
-> (forall x. Rep TsoFlags x -> TsoFlags) -> Generic TsoFlags
forall x. Rep TsoFlags x -> TsoFlags
forall x. TsoFlags -> Rep TsoFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TsoFlags -> Rep TsoFlags x
from :: forall x. TsoFlags -> Rep TsoFlags x
$cto :: forall x. Rep TsoFlags x -> TsoFlags
to :: forall x. Rep TsoFlags x -> TsoFlags
Generic, Eq TsoFlags
Eq TsoFlags =>
(TsoFlags -> TsoFlags -> Ordering)
-> (TsoFlags -> TsoFlags -> Bool)
-> (TsoFlags -> TsoFlags -> Bool)
-> (TsoFlags -> TsoFlags -> Bool)
-> (TsoFlags -> TsoFlags -> Bool)
-> (TsoFlags -> TsoFlags -> TsoFlags)
-> (TsoFlags -> TsoFlags -> TsoFlags)
-> Ord TsoFlags
TsoFlags -> TsoFlags -> Bool
TsoFlags -> TsoFlags -> Ordering
TsoFlags -> TsoFlags -> TsoFlags
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TsoFlags -> TsoFlags -> Ordering
compare :: TsoFlags -> TsoFlags -> Ordering
$c< :: TsoFlags -> TsoFlags -> Bool
< :: TsoFlags -> TsoFlags -> Bool
$c<= :: TsoFlags -> TsoFlags -> Bool
<= :: TsoFlags -> TsoFlags -> Bool
$c> :: TsoFlags -> TsoFlags -> Bool
> :: TsoFlags -> TsoFlags -> Bool
$c>= :: TsoFlags -> TsoFlags -> Bool
>= :: TsoFlags -> TsoFlags -> Bool
$cmax :: TsoFlags -> TsoFlags -> TsoFlags
max :: TsoFlags -> TsoFlags -> TsoFlags
$cmin :: TsoFlags -> TsoFlags -> TsoFlags
min :: TsoFlags -> TsoFlags -> TsoFlags
Ord)
allClosures :: GenClosure b -> [b]
allClosures :: forall b. GenClosure b -> [b]
allClosures (ConstrClosure {[b]
String
[Word]
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
ptrArgs :: forall b. GenClosure b -> [b]
dataArgs :: forall b. GenClosure b -> [Word]
pkg :: forall b. GenClosure b -> String
modl :: forall b. GenClosure b -> String
name :: forall b. GenClosure b -> String
info :: StgInfoTable
ptrArgs :: [b]
dataArgs :: [Word]
pkg :: String
modl :: String
name :: String
..}) = [b]
ptrArgs
allClosures (ThunkClosure {[b]
[Word]
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
ptrArgs :: forall b. GenClosure b -> [b]
dataArgs :: forall b. GenClosure b -> [Word]
info :: StgInfoTable
ptrArgs :: [b]
dataArgs :: [Word]
..}) = [b]
ptrArgs
allClosures (SelectorClosure {b
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
selectee :: forall b. GenClosure b -> b
info :: StgInfoTable
selectee :: b
..}) = [b
selectee]
allClosures (IndClosure {b
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
indirectee :: forall b. GenClosure b -> b
info :: StgInfoTable
indirectee :: b
..}) = [b
indirectee]
allClosures (BlackholeClosure {b
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
indirectee :: forall b. GenClosure b -> b
info :: StgInfoTable
indirectee :: b
..}) = [b
indirectee]
allClosures (APClosure {b
[b]
StgInfoTable
HalfWord
info :: forall b. GenClosure b -> StgInfoTable
arity :: forall b. GenClosure b -> HalfWord
n_args :: forall b. GenClosure b -> HalfWord
fun :: forall b. GenClosure b -> b
payload :: forall b. GenClosure b -> [b]
info :: StgInfoTable
arity :: HalfWord
n_args :: HalfWord
fun :: b
payload :: [b]
..}) = b
funb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
payload
allClosures (PAPClosure {b
[b]
StgInfoTable
HalfWord
info :: forall b. GenClosure b -> StgInfoTable
arity :: forall b. GenClosure b -> HalfWord
n_args :: forall b. GenClosure b -> HalfWord
fun :: forall b. GenClosure b -> b
payload :: forall b. GenClosure b -> [b]
info :: StgInfoTable
arity :: HalfWord
n_args :: HalfWord
fun :: b
payload :: [b]
..}) = b
funb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
payload
allClosures (APStackClosure {b
[b]
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
fun :: forall b. GenClosure b -> b
payload :: forall b. GenClosure b -> [b]
info :: StgInfoTable
fun :: b
payload :: [b]
..}) = b
funb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
payload
allClosures (BCOClosure {b
[Word]
StgInfoTable
HalfWord
info :: forall b. GenClosure b -> StgInfoTable
arity :: forall b. GenClosure b -> HalfWord
instrs :: forall b. GenClosure b -> b
literals :: forall b. GenClosure b -> b
bcoptrs :: forall b. GenClosure b -> b
size :: forall b. GenClosure b -> HalfWord
bitmap :: forall b. GenClosure b -> [Word]
info :: StgInfoTable
instrs :: b
literals :: b
bcoptrs :: b
arity :: HalfWord
size :: HalfWord
bitmap :: [Word]
..}) = [b
instrs,b
literals,b
bcoptrs]
allClosures (ArrWordsClosure {}) = []
allClosures (MutArrClosure {[b]
Word
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
mccPtrs :: forall b. GenClosure b -> Word
mccSize :: forall b. GenClosure b -> Word
mccPayload :: forall b. GenClosure b -> [b]
info :: StgInfoTable
mccPtrs :: Word
mccSize :: Word
mccPayload :: [b]
..}) = [b]
mccPayload
allClosures (SmallMutArrClosure {[b]
Word
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
mccPtrs :: forall b. GenClosure b -> Word
mccPayload :: forall b. GenClosure b -> [b]
info :: StgInfoTable
mccPtrs :: Word
mccPayload :: [b]
..}) = [b]
mccPayload
allClosures (MutVarClosure {b
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
var :: forall b. GenClosure b -> b
info :: StgInfoTable
var :: b
..}) = [b
var]
allClosures (MVarClosure {b
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
queueHead :: forall b. GenClosure b -> b
queueTail :: forall b. GenClosure b -> b
value :: forall b. GenClosure b -> b
info :: StgInfoTable
queueHead :: b
queueTail :: b
value :: b
..}) = [b
queueHead,b
queueTail,b
value]
allClosures (FunClosure {[b]
[Word]
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
ptrArgs :: forall b. GenClosure b -> [b]
dataArgs :: forall b. GenClosure b -> [Word]
info :: StgInfoTable
ptrArgs :: [b]
dataArgs :: [Word]
..}) = [b]
ptrArgs
allClosures (BlockingQueueClosure {b
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
link :: forall b. GenClosure b -> b
blackHole :: forall b. GenClosure b -> b
owner :: forall b. GenClosure b -> b
queue :: forall b. GenClosure b -> b
info :: StgInfoTable
link :: b
blackHole :: b
owner :: b
queue :: b
..}) = [b
link, b
blackHole, b
owner, b
queue]
allClosures (WeakClosure {b
Maybe b
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
value :: forall b. GenClosure b -> b
cfinalizers :: forall b. GenClosure b -> b
key :: forall b. GenClosure b -> b
finalizer :: forall b. GenClosure b -> b
weakLink :: forall b. GenClosure b -> Maybe b
info :: StgInfoTable
cfinalizers :: b
key :: b
value :: b
finalizer :: b
weakLink :: Maybe b
..}) = [b
cfinalizers, b
key, b
value, b
finalizer] [b] -> [b] -> [b]
forall a. [a] -> [a] -> [a]
++ Maybe b -> [b]
forall a. Maybe a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
GHC.Internal.Data.Foldable.toList Maybe b
weakLink
allClosures (OtherClosure {[b]
[Word]
StgInfoTable
info :: forall b. GenClosure b -> StgInfoTable
hvalues :: forall b. GenClosure b -> [b]
rawWords :: forall b. GenClosure b -> [Word]
info :: StgInfoTable
hvalues :: [b]
rawWords :: [Word]
..}) = [b]
hvalues
allClosures GenClosure b
_ = []
closureSize :: Box -> Int
closureSize :: Box -> Int
closureSize (Box Any
x) = Int# -> Int
I# (Any -> Int#
forall a. a -> Int#
closureSize# Any
x)