{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ExistentialQuantification #-}
module GHC.Debug.Stub (withGhcDebug, saveClosures, Box(..), pause, resume) where
import Control.Applicative
import Control.Concurrent
import Control.Monad
import Data.Maybe (fromMaybe)
import Foreign.C.Types
import Foreign.C.String
import Foreign.Marshal.Array
import Foreign.StablePtr
import GHC.Exts
import GHC.Int
import GHC.IO
import GHC.Prim
import System.FilePath
import System.Directory
import System.Environment
import System.Mem
import System.IO
import GHC.Debug.Convention (socketDirectory)
foreign import ccall safe "start"
start_c :: CString -> IO ()
foreign import ccall safe "unistd.h getpid"
getpid_c :: IO CInt
withGhcDebug :: IO a -> IO a
withGhcDebug :: forall a. IO a -> IO a
withGhcDebug IO a
main = do
String
socketPath <- do
String
socketOverride <- forall a. a -> Maybe a -> a
fromMaybe String
"" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv String
"GHC_DEBUG_SOCKET"
if Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
socketOverride)
then forall (m :: * -> *) a. Monad m => a -> m a
return String
socketOverride
else do
String
dir <- IO String
socketDirectory
String
name <- IO String
getProgName
String
pid <- forall a. Show a => a -> String
show forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO CInt
getpid_c
let socketName :: String
socketName = String
pid forall a. [a] -> [a] -> [a]
++ String
"-" forall a. [a] -> [a] -> [a]
++ String
name
forall (m :: * -> *) a. Monad m => a -> m a
return (String
dir String -> String -> String
</> String
socketName)
Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
socketPath)
Handle -> String -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ String
"Starting ghc-debug on socket: " forall a. [a] -> [a] -> [a]
++ String
socketPath
ThreadId
_threadId <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ forall a. String -> (CString -> IO a) -> IO a
withCString String
socketPath CString -> IO ()
start_c
IO a
main
forall a b. IO a -> IO b -> IO a
`finally`
(String -> IO ()
removeFile String
socketPath
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String -> IO ()
putStrLn (String
"ghc-debug: failed to cleanup socket: " forall a. [a] -> [a] -> [a]
++ String
socketPath)
)
foreign import ccall safe "pause_mutator"
pause_c :: IO ()
pause :: IO ()
pause :: IO ()
pause = IO ()
performGC forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
pause_c
foreign import ccall safe "resume_mutator"
resume :: IO ()
foreign import ccall unsafe "saveClosures" c_saveClosures
:: CInt -> Ptr (Ptr ()) -> IO ()
data Box = forall a . Box a
unbox :: (forall a . a -> b) -> Box -> b
unbox :: forall b. (forall a. a -> b) -> Box -> b
unbox forall a. a -> b
f (Box a
a) = forall a. a -> b
f a
a
saveClosures :: [Box] -> IO ()
saveClosures :: [Box] -> IO ()
saveClosures [Box]
xs = do
[Ptr ()]
sps <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\(Box a
x) -> forall a. StablePtr a -> Ptr ()
castStablePtrToPtr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. a -> IO (StablePtr a)
newStablePtr a
x) [Box]
xs
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [Ptr ()]
sps forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr ())
sps_arr ->
CInt -> Ptr (Ptr ()) -> IO ()
c_saveClosures (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Box]
xs)) Ptr (Ptr ())
sps_arr