{-# LANGUAGE CPP, UnboxedTuples, MagicHash #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module GHCi.ObjLink
( initObjLinker, ShouldRetainCAFs(..)
, loadDLL
, loadArchive
, loadObj
, unloadObj
, purgeObj
, lookupSymbol
, lookupClosure
, resolveObjs
, addLibrarySearchPath
, removeLibrarySearchPath
, findSystemLibrary
) where
import Prelude
import GHCi.RemoteTypes
import Control.Exception (throwIO, ErrorCall(..))
import Control.Monad ( when )
import Foreign.C
import Foreign.Marshal.Alloc ( free )
import Foreign ( nullPtr )
import GHC.Exts
import System.Posix.Internals ( CFilePath, withFilePath, peekFilePath )
import System.FilePath ( dropExtension, normalise )
data ShouldRetainCAFs
= RetainCAFs
| DontRetainCAFs
initObjLinker :: ShouldRetainCAFs -> IO ()
initObjLinker :: ShouldRetainCAFs -> IO ()
initObjLinker ShouldRetainCAFs
RetainCAFs = CInt -> IO ()
c_initLinker_ CInt
1
initObjLinker ShouldRetainCAFs
_ = CInt -> IO ()
c_initLinker_ CInt
0
lookupSymbol :: String -> IO (Maybe (Ptr a))
lookupSymbol :: forall a. String -> IO (Maybe (Ptr a))
lookupSymbol String
str_in = do
let str :: String
str = String -> String
prefixUnderscore String
str_in
String -> (CFilePath -> IO (Maybe (Ptr a))) -> IO (Maybe (Ptr a))
forall a. String -> (CFilePath -> IO a) -> IO a
withCAString String
str ((CFilePath -> IO (Maybe (Ptr a))) -> IO (Maybe (Ptr a)))
-> (CFilePath -> IO (Maybe (Ptr a))) -> IO (Maybe (Ptr a))
forall a b. (a -> b) -> a -> b
$ \CFilePath
c_str -> do
addr <- CFilePath -> IO (Ptr a)
forall a. CFilePath -> IO (Ptr a)
c_lookupSymbol CFilePath
c_str
if addr == nullPtr
then return Nothing
else return (Just addr)
lookupClosure :: String -> IO (Maybe HValueRef)
lookupClosure :: String -> IO (Maybe HValueRef)
lookupClosure String
str = do
m <- String -> IO (Maybe (Ptr Any))
forall a. String -> IO (Maybe (Ptr a))
lookupSymbol String
str
case m of
Maybe (Ptr Any)
Nothing -> Maybe HValueRef -> IO (Maybe HValueRef)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe HValueRef
forall a. Maybe a
Nothing
Just (Ptr Addr#
addr) -> case Addr# -> (# Any #)
forall a. Addr# -> (# a #)
addrToAny# Addr#
addr of
(# Any
a #) -> HValueRef -> Maybe HValueRef
forall a. a -> Maybe a
Just (HValueRef -> Maybe HValueRef)
-> IO HValueRef -> IO (Maybe HValueRef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HValue -> IO HValueRef
forall a. a -> IO (RemoteRef a)
mkRemoteRef (Any -> HValue
HValue Any
a)
prefixUnderscore :: String -> String
prefixUnderscore :: String -> String
prefixUnderscore
| Bool
cLeadingUnderscore = (Char
'_'Char -> String -> String
forall a. a -> [a] -> [a]
:)
| Bool
otherwise = String -> String
forall a. a -> a
id
loadDLL :: String -> IO (Maybe String)
loadDLL :: String -> IO (Maybe String)
loadDLL String
str0 = do
let
str :: String
str | Bool
isWindowsHost = String -> String
dropExtension String
str0
| Bool
otherwise = String
str0
maybe_errmsg <- String -> (CFilePath -> IO CFilePath) -> IO CFilePath
forall a. String -> (CFilePath -> IO a) -> IO a
withFilePath (String -> String
normalise String
str) ((CFilePath -> IO CFilePath) -> IO CFilePath)
-> (CFilePath -> IO CFilePath) -> IO CFilePath
forall a b. (a -> b) -> a -> b
$ \CFilePath
dll -> CFilePath -> IO CFilePath
c_addDLL CFilePath
dll
if maybe_errmsg == nullPtr
then return Nothing
else do str <- peekCString maybe_errmsg
free maybe_errmsg
return (Just str)
loadArchive :: String -> IO ()
loadArchive :: String -> IO ()
loadArchive String
str = do
String -> (CFilePath -> IO ()) -> IO ()
forall a. String -> (CFilePath -> IO a) -> IO a
withFilePath String
str ((CFilePath -> IO ()) -> IO ()) -> (CFilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CFilePath
c_str -> do
r <- CFilePath -> IO Int
c_loadArchive CFilePath
c_str
when (r == 0) (throwIO (ErrorCall ("loadArchive " ++ show str ++ ": failed")))
loadObj :: String -> IO ()
loadObj :: String -> IO ()
loadObj String
str = do
String -> (CFilePath -> IO ()) -> IO ()
forall a. String -> (CFilePath -> IO a) -> IO a
withFilePath String
str ((CFilePath -> IO ()) -> IO ()) -> (CFilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CFilePath
c_str -> do
r <- CFilePath -> IO Int
c_loadObj CFilePath
c_str
when (r == 0) (throwIO (ErrorCall ("loadObj " ++ show str ++ ": failed")))
unloadObj :: String -> IO ()
unloadObj :: String -> IO ()
unloadObj String
str =
String -> (CFilePath -> IO ()) -> IO ()
forall a. String -> (CFilePath -> IO a) -> IO a
withFilePath String
str ((CFilePath -> IO ()) -> IO ()) -> (CFilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CFilePath
c_str -> do
r <- CFilePath -> IO Int
c_unloadObj CFilePath
c_str
when (r == 0) (throwIO (ErrorCall ("unloadObj " ++ show str ++ ": failed")))
purgeObj :: String -> IO ()
purgeObj :: String -> IO ()
purgeObj String
str =
String -> (CFilePath -> IO ()) -> IO ()
forall a. String -> (CFilePath -> IO a) -> IO a
withFilePath String
str ((CFilePath -> IO ()) -> IO ()) -> (CFilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CFilePath
c_str -> do
r <- CFilePath -> IO Int
c_purgeObj CFilePath
c_str
when (r == 0) (throwIO (ErrorCall ("purgeObj " ++ show str ++ ": failed")))
addLibrarySearchPath :: String -> IO (Ptr ())
addLibrarySearchPath :: String -> IO (Ptr ())
addLibrarySearchPath String
str =
String -> (CFilePath -> IO (Ptr ())) -> IO (Ptr ())
forall a. String -> (CFilePath -> IO a) -> IO a
withFilePath String
str CFilePath -> IO (Ptr ())
c_addLibrarySearchPath
removeLibrarySearchPath :: Ptr () -> IO Bool
removeLibrarySearchPath :: Ptr () -> IO Bool
removeLibrarySearchPath = Ptr () -> IO Bool
c_removeLibrarySearchPath
findSystemLibrary :: String -> IO (Maybe String)
findSystemLibrary :: String -> IO (Maybe String)
findSystemLibrary String
str = do
result <- String -> (CFilePath -> IO CFilePath) -> IO CFilePath
forall a. String -> (CFilePath -> IO a) -> IO a
withFilePath String
str CFilePath -> IO CFilePath
c_findSystemLibrary
case result == nullPtr of
Bool
True -> Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
Bool
False -> do path <- CFilePath -> IO String
peekFilePath CFilePath
result
free result
return $ Just path
resolveObjs :: IO Bool
resolveObjs :: IO Bool
resolveObjs = do
r <- IO Int
c_resolveObjs
return (r /= 0)
foreign import ccall unsafe "addDLL" c_addDLL :: CFilePath -> IO CString
foreign import ccall unsafe "initLinker_" c_initLinker_ :: CInt -> IO ()
foreign import ccall unsafe "lookupSymbol" c_lookupSymbol :: CString -> IO (Ptr a)
foreign import ccall unsafe "loadArchive" c_loadArchive :: CFilePath -> IO Int
foreign import ccall unsafe "loadObj" c_loadObj :: CFilePath -> IO Int
foreign import ccall unsafe "purgeObj" c_purgeObj :: CFilePath -> IO Int
foreign import ccall unsafe "unloadObj" c_unloadObj :: CFilePath -> IO Int
foreign import ccall unsafe "resolveObjs" c_resolveObjs :: IO Int
foreign import ccall unsafe "addLibrarySearchPath" c_addLibrarySearchPath :: CFilePath -> IO (Ptr ())
foreign import ccall unsafe "findSystemLibrary" c_findSystemLibrary :: CFilePath -> IO CFilePath
foreign import ccall unsafe "removeLibrarySearchPath" c_removeLibrarySearchPath :: Ptr() -> IO Bool
#include "ghcautoconf.h"
cLeadingUnderscore :: Bool
#if defined(LEADING_UNDERSCORE)
cLeadingUnderscore = True
#else
cLeadingUnderscore :: Bool
cLeadingUnderscore = Bool
False
#endif
isWindowsHost :: Bool
#if defined(mingw32_HOST_OS)
isWindowsHost = True
#else
isWindowsHost :: Bool
isWindowsHost = Bool
False
#endif