{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes#-}
{-# LANGUAGE GHCForeignImportPrim #-}
module GHC.Internal.Stack.CloneStack (
StackSnapshot(..),
StackEntry(..),
cloneMyStack,
cloneThreadStack,
decode,
prettyStackEntry
) where
import GHC.Internal.MVar
import GHC.Internal.Data.Maybe (catMaybes)
import GHC.Internal.Base
import GHC.Internal.Foreign.Storable
import GHC.Internal.Conc.Sync
import GHC.Internal.IO (unsafeInterleaveIO)
import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE, StgInfoTable)
import GHC.Internal.Num
import GHC.Internal.Real (div)
import GHC.Internal.Stable
import GHC.Internal.Text.Show
import GHC.Internal.Ptr
import GHC.Internal.ClosureTypes
data StackSnapshot = StackSnapshot !StackSnapshot#
foreign import prim "stg_decodeStackzh" decodeStack# :: StackSnapshot# -> State# RealWorld -> (# State# RealWorld, ByteArray# #)
foreign import prim "stg_cloneMyStackzh" cloneMyStack# :: State# RealWorld -> (# State# RealWorld, StackSnapshot# #)
foreign import prim "stg_sendCloneStackMessagezh" sendCloneStackMessage# :: ThreadId# -> StablePtr# PrimMVar -> State# RealWorld -> (# State# RealWorld, (# #) #)
cloneMyStack :: IO StackSnapshot
cloneMyStack :: IO StackSnapshot
cloneMyStack = (State# RealWorld -> (# State# RealWorld, StackSnapshot #))
-> IO StackSnapshot
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, StackSnapshot #))
-> IO StackSnapshot)
-> (State# RealWorld -> (# State# RealWorld, StackSnapshot #))
-> IO StackSnapshot
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case (State# RealWorld -> (# State# RealWorld, StackSnapshot# #)
cloneMyStack# State# RealWorld
s) of (# State# RealWorld
s1, StackSnapshot#
stack #) -> (# State# RealWorld
s1, StackSnapshot# -> StackSnapshot
StackSnapshot StackSnapshot#
stack #)
cloneThreadStack :: ThreadId -> IO StackSnapshot
cloneThreadStack :: ThreadId -> IO StackSnapshot
cloneThreadStack (ThreadId ThreadId#
tid#) = do
resultVar <- forall a. IO (MVar a)
newEmptyMVar @StackSnapshot
boxedPtr@(StablePtr ptr) <- newStablePtrPrimMVar resultVar
IO $ \State# RealWorld
s -> case ThreadId#
-> StablePtr# PrimMVar
-> State# RealWorld
-> (# State# RealWorld, (# #) #)
sendCloneStackMessage# ThreadId#
tid# StablePtr# PrimMVar
ptr State# RealWorld
s of (# State# RealWorld
s', (# #) #) -> (# State# RealWorld
s', () #)
freeStablePtr boxedPtr
takeMVar resultVar
data StackEntry = StackEntry
{ StackEntry -> String
functionName :: String,
StackEntry -> String
moduleName :: String,
StackEntry -> String
srcLoc :: String,
StackEntry -> ClosureType
closureType :: ClosureType
}
deriving (Int -> StackEntry -> ShowS
[StackEntry] -> ShowS
StackEntry -> String
(Int -> StackEntry -> ShowS)
-> (StackEntry -> String)
-> ([StackEntry] -> ShowS)
-> Show StackEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StackEntry -> ShowS
showsPrec :: Int -> StackEntry -> ShowS
$cshow :: StackEntry -> String
show :: StackEntry -> String
$cshowList :: [StackEntry] -> ShowS
showList :: [StackEntry] -> ShowS
Show, StackEntry -> StackEntry -> Bool
(StackEntry -> StackEntry -> Bool)
-> (StackEntry -> StackEntry -> Bool) -> Eq StackEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StackEntry -> StackEntry -> Bool
== :: StackEntry -> StackEntry -> Bool
$c/= :: StackEntry -> StackEntry -> Bool
/= :: StackEntry -> StackEntry -> Bool
Eq)
decode :: StackSnapshot -> IO [StackEntry]
decode :: StackSnapshot -> IO [StackEntry]
decode StackSnapshot
stackSnapshot = [Maybe StackEntry] -> [StackEntry]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe StackEntry] -> [StackEntry])
-> IO [Maybe StackEntry] -> IO [StackEntry]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` StackSnapshot -> IO [Maybe StackEntry]
getDecodedStackArray StackSnapshot
stackSnapshot
toStackEntry :: InfoProv -> StackEntry
toStackEntry :: InfoProv -> StackEntry
toStackEntry InfoProv
infoProv =
StackEntry
{ functionName :: String
functionName = InfoProv -> String
ipLabel InfoProv
infoProv,
moduleName :: String
moduleName = InfoProv -> String
ipMod InfoProv
infoProv,
srcLoc :: String
srcLoc = InfoProv -> String
ipLoc InfoProv
infoProv,
closureType :: ClosureType
closureType = InfoProv -> ClosureType
ipDesc InfoProv
infoProv
}
getDecodedStackArray :: StackSnapshot -> IO [Maybe StackEntry]
getDecodedStackArray :: StackSnapshot -> IO [Maybe StackEntry]
getDecodedStackArray (StackSnapshot StackSnapshot#
s) =
(State# RealWorld -> (# State# RealWorld, [Maybe StackEntry] #))
-> IO [Maybe StackEntry]
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, [Maybe StackEntry] #))
-> IO [Maybe StackEntry])
-> (State# RealWorld -> (# State# RealWorld, [Maybe StackEntry] #))
-> IO [Maybe StackEntry]
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s0 -> case StackSnapshot#
-> State# RealWorld -> (# State# RealWorld, ByteArray# #)
decodeStack# StackSnapshot#
s State# RealWorld
s0 of
(# State# RealWorld
s1, ByteArray#
arr #) ->
let n :: Int
n = Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
wordSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
in IO [Maybe StackEntry]
-> State# RealWorld -> (# State# RealWorld, [Maybe StackEntry] #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (ByteArray# -> Int -> IO [Maybe StackEntry]
go ByteArray#
arr Int
n) State# RealWorld
s1
where
go :: ByteArray# -> Int -> IO [Maybe StackEntry]
go :: ByteArray# -> Int -> IO [Maybe StackEntry]
go ByteArray#
_stack (-1) = [Maybe StackEntry] -> IO [Maybe StackEntry]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
go ByteArray#
stack Int
i = do
infoProv <- Ptr StgInfoTable -> IO (Maybe InfoProv)
lookupIPE (ByteArray# -> Int -> Ptr StgInfoTable
stackEntryAt ByteArray#
stack Int
i)
rest <- unsafeInterleaveIO $ go stack (i-1)
return ((toStackEntry `fmap` infoProv) : rest)
stackEntryAt :: ByteArray# -> Int -> Ptr StgInfoTable
stackEntryAt :: ByteArray# -> Int -> Ptr StgInfoTable
stackEntryAt ByteArray#
stack (I# Int#
i) = Addr# -> Ptr StgInfoTable
forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Int# -> Addr#
indexAddrArray# ByteArray#
stack Int#
i)
wordSize :: Int
wordSize = Ptr () -> Int
forall a. Storable a => a -> Int
sizeOf (Ptr ()
forall a. Ptr a
nullPtr :: Ptr ())
prettyStackEntry :: StackEntry -> String
prettyStackEntry :: StackEntry -> String
prettyStackEntry (StackEntry {moduleName :: StackEntry -> String
moduleName=String
mod_nm, functionName :: StackEntry -> String
functionName=String
fun_nm, srcLoc :: StackEntry -> String
srcLoc=String
loc}) =
String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
mod_nm String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"." String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
fun_nm String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
loc String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"