{-# LINE 1 "libraries/unix/System/Posix/DynamicLinker/Module/ByteString.hsc" #-} {-# LANGUAGE Safe #-} ----------------------------------------------------------------------------- -- | -- Module : System.Posix.DynamicLinker.Module.ByteString -- Copyright : (c) Volker Stolz <vs@foldr.org> 2003 -- License : BSD-style (see the file libraries/base/LICENSE) -- -- Maintainer : vs@foldr.org -- Stability : provisional -- Portability : non-portable (requires POSIX) -- -- DLOpen support, old API -- Derived from GModule.chs by M.Weber & M.Chakravarty which is part of c2hs -- I left the API more or less the same, mostly the flags are different. -- ----------------------------------------------------------------------------- module System.Posix.DynamicLinker.Module.ByteString ( -- Usage: -- ****** -- -- Let's assume you want to open a local shared library 'foo' (./libfoo.so) -- offering a function -- char * mogrify (char*,int) -- and invoke str = mogrify("test",1): -- -- type Fun = CString -> Int -> IO CString -- foreign import dynamic unsafe fun__ :: FunPtr Fun -> Fun -- -- withModule (Just ".") ("libfoo.so") [RTLD_NOW] $ \ mod -> do -- funptr <- moduleSymbol mod "mogrify" -- let fun = fun__ funptr -- withCString "test" $ \ str -> do -- strptr <- fun str 1 -- strstr <- peekCString strptr -- ... Module , moduleOpen -- :: String -> ModuleFlags -> IO Module , moduleSymbol -- :: Source -> String -> IO (FunPtr a) , moduleClose -- :: Module -> IO Bool , moduleError -- :: IO String , withModule -- :: Maybe String -- -> String -- -> [ModuleFlags ] -- -> (Module -> IO a) -- -> IO a , withModule_ -- :: Maybe String -- -> String -- -> [ModuleFlags] -- -> (Module -> IO a) -- -> IO () ) where import System.Posix.DynamicLinker.Module hiding (moduleOpen) import System.Posix.DynamicLinker.Prim import System.Posix.DynamicLinker.Common import Foreign import System.Posix.ByteString.FilePath -- Opens a module (EXPORTED) -- moduleOpen :: RawFilePath -> [RTLDFlags] -> IO Module moduleOpen :: RawFilePath -> [RTLDFlags] -> IO Module moduleOpen RawFilePath file [RTLDFlags] flags = do modPtr <- RawFilePath -> (CString -> IO (Ptr ())) -> IO (Ptr ()) forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath file ((CString -> IO (Ptr ())) -> IO (Ptr ())) -> (CString -> IO (Ptr ())) -> IO (Ptr ()) forall a b. (a -> b) -> a -> b $ \ CString modAddr -> CString -> CInt -> IO (Ptr ()) c_dlopen CString modAddr ([RTLDFlags] -> CInt packRTLDFlags [RTLDFlags] flags) if (modPtr == nullPtr) then moduleError >>= \ String err -> IOError -> IO Module forall a. HasCallStack => IOError -> IO a ioError (String -> IOError userError (String "dlopen: " String -> String -> String forall a. [a] -> [a] -> [a] ++ String err)) else return $ Module modPtr