aboutsummaryrefslogtreecommitdiffhomepage
path: root/System/Posix/DynamicLinker
diff options
context:
space:
mode:
authorGravatar Simon Marlow <marlowsd@gmail.com>2011-11-11 16:18:48 +0000
committerGravatar Simon Marlow <marlowsd@gmail.com>2011-11-22 12:36:48 +0000
commit34c7bf896f19b182cf6fa104e057f1df9df1254a (patch)
treeabdb8264ae52c62263fc0fb4b395906a64acb104 /System/Posix/DynamicLinker
parentc213ae2ec6d9c71266aebc8e5b2326a9625fba7a (diff)
Provide a raw ByteString version of FilePath and environment APIs
The new module System.Posix.ByteString provides exactly the same API as System.Posix, except that: - There is a new type: RawFilePath = ByteString - All functions mentioning FilePath in the System.Posix API use RawFilePath in the System.Posix.ByteString API - RawFilePaths are not subject to Unicode locale encoding and decoding, unlike FilePaths. They are the exact bytes passed to and returned from the underlying POSIX API. - Similarly for functions that deal in environment strings (System.Posix.Env): these use untranslated ByteStrings in System.Posix.Environment - There is a new function System.Posix.ByteString.getArgs :: [ByteString] returning the raw untranslated arguments as passed to exec() when the program was started.
Diffstat (limited to 'System/Posix/DynamicLinker')
-rw-r--r--System/Posix/DynamicLinker/ByteString.hsc70
-rw-r--r--System/Posix/DynamicLinker/Common.hsc90
-rw-r--r--System/Posix/DynamicLinker/Module.hsc7
-rw-r--r--System/Posix/DynamicLinker/Module/ByteString.hsc77
-rw-r--r--System/Posix/DynamicLinker/Prim.hsc2
5 files changed, 240 insertions, 6 deletions
diff --git a/System/Posix/DynamicLinker/ByteString.hsc b/System/Posix/DynamicLinker/ByteString.hsc
new file mode 100644
index 0000000..6525eb9
--- /dev/null
+++ b/System/Posix/DynamicLinker/ByteString.hsc
@@ -0,0 +1,70 @@
+#if __GLASGOW_HASKELL__ >= 701
+{-# LANGUAGE Trustworthy #-}
+#endif
+-----------------------------------------------------------------------------
+-- |
+-- Module : System.Posix.DynamicLinker.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)
+--
+-- Dynamic linker support through dlopen()
+-----------------------------------------------------------------------------
+
+module System.Posix.DynamicLinker.ByteString (
+
+ module System.Posix.DynamicLinker.Prim,
+ dlopen,
+ dlsym,
+ dlerror,
+ dlclose,
+ withDL, withDL_,
+ undl,
+ )
+
+-- 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
+--
+-- withDL "libfoo.so" [RTLD_NOW] \$ \\ mod -> do
+-- funptr <- dlsym mod "mogrify"
+-- let fun = fun__ funptr
+-- withCString "test" \$ \\ str -> do
+-- strptr <- fun str 1
+-- strstr <- peekCString strptr
+-- ...
+--
+
+where
+
+import System.Posix.DynamicLinker.Common
+import System.Posix.DynamicLinker.Prim
+
+#include "HsUnix.h"
+
+import Control.Exception ( bracket )
+import Control.Monad ( liftM )
+import Foreign
+import System.Posix.ByteString.FilePath
+
+dlopen :: RawFilePath -> [RTLDFlags] -> IO DL
+dlopen path flags = do
+ withFilePath path $ \ p -> do
+ liftM DLHandle $ throwDLErrorIf "dlopen" (== nullPtr) $ c_dlopen p (packRTLDFlags flags)
+
+withDL :: RawFilePath -> [RTLDFlags] -> (DL -> IO a) -> IO a
+withDL file flags f = bracket (dlopen file flags) (dlclose) f
+
+withDL_ :: RawFilePath -> [RTLDFlags] -> (DL -> IO a) -> IO ()
+withDL_ file flags f = withDL file flags f >> return ()
diff --git a/System/Posix/DynamicLinker/Common.hsc b/System/Posix/DynamicLinker/Common.hsc
new file mode 100644
index 0000000..2b5e0d9
--- /dev/null
+++ b/System/Posix/DynamicLinker/Common.hsc
@@ -0,0 +1,90 @@
+#if __GLASGOW_HASKELL__ >= 701
+{-# LANGUAGE Trustworthy #-}
+#endif
+-----------------------------------------------------------------------------
+-- |
+-- Module : System.Posix.DynamicLinker.Common
+-- 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)
+--
+-- Dynamic linker support through dlopen()
+-----------------------------------------------------------------------------
+
+module System.Posix.DynamicLinker.Common (
+
+ module System.Posix.DynamicLinker.Prim,
+ dlsym,
+ dlerror,
+ dlclose,
+ undl,
+ throwDLErrorIf,
+ Module(..)
+ )
+
+-- 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
+--
+-- withDL "libfoo.so" [RTLD_NOW] \$ \\ mod -> do
+-- funptr <- dlsym mod "mogrify"
+-- let fun = fun__ funptr
+-- withCString "test" \$ \\ str -> do
+-- strptr <- fun str 1
+-- strstr <- peekCString strptr
+-- ...
+--
+
+where
+
+#include "HsUnix.h"
+
+import System.Posix.DynamicLinker.Prim
+import Foreign
+import Foreign.C
+
+dlclose :: DL -> IO ()
+dlclose (DLHandle h) = throwDLErrorIf_ "dlclose" (/= 0) $ c_dlclose h
+dlclose h = error $ "dlclose: invalid argument" ++ (show h)
+
+dlerror :: IO String
+dlerror = c_dlerror >>= peekCString
+
+-- |'dlsym' returns the address binding of the symbol described in @symbol@,
+-- as it occurs in the shared object identified by @source@.
+
+dlsym :: DL -> String -> IO (FunPtr a)
+dlsym source symbol = do
+ withCAString symbol $ \ s -> do
+ throwDLErrorIf "dlsym" (== nullFunPtr) $ c_dlsym (packDL source) s
+
+-- |'undl' obtains the raw handle. You mustn't do something like
+-- @withDL mod flags $ liftM undl >>= \ p -> use p@
+
+undl :: DL -> Ptr ()
+undl = packDL
+
+throwDLErrorIf :: String -> (a -> Bool) -> IO a -> IO a
+throwDLErrorIf s p f = do
+ r <- f
+ if (p r)
+ then dlerror >>= \ err -> ioError (userError ( s ++ ": " ++ err))
+ else return r
+
+throwDLErrorIf_ :: String -> (a -> Bool) -> IO a -> IO ()
+throwDLErrorIf_ s p f = throwDLErrorIf s p f >> return ()
+
+-- abstract handle for dynamically loaded module (EXPORTED)
+--
+newtype Module = Module (Ptr ())
diff --git a/System/Posix/DynamicLinker/Module.hsc b/System/Posix/DynamicLinker/Module.hsc
index c678fed..2e5d6fe 100644
--- a/System/Posix/DynamicLinker/Module.hsc
+++ b/System/Posix/DynamicLinker/Module.hsc
@@ -60,7 +60,8 @@ where
#include "HsUnix.h"
import System.Posix.DynamicLinker
-import Foreign.Ptr ( Ptr, nullPtr, FunPtr )
+import System.Posix.DynamicLinker.Common
+import Foreign.Ptr ( Ptr, nullPtr, FunPtr )
#if __GLASGOW_HASKELL__ > 611
import System.Posix.Internals ( withFilePath )
#else
@@ -70,10 +71,6 @@ withFilePath :: FilePath -> (CString -> IO a) -> IO a
withFilePath = withCString
#endif
--- abstract handle for dynamically loaded module (EXPORTED)
---
-newtype Module = Module (Ptr ())
-
unModule :: Module -> (Ptr ())
unModule (Module adr) = adr
diff --git a/System/Posix/DynamicLinker/Module/ByteString.hsc b/System/Posix/DynamicLinker/Module/ByteString.hsc
new file mode 100644
index 0000000..59f45e2
--- /dev/null
+++ b/System/Posix/DynamicLinker/Module/ByteString.hsc
@@ -0,0 +1,77 @@
+{-# LANGUAGE ForeignFunctionInterface #-}
+#if __GLASGOW_HASKELL__ >= 701
+{-# LANGUAGE Trustworthy #-}
+#endif
+-----------------------------------------------------------------------------
+-- |
+-- 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
+
+#include "HsUnix.h"
+
+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 file flags = do
+ modPtr <- withFilePath file $ \ modAddr -> c_dlopen modAddr (packRTLDFlags flags)
+ if (modPtr == nullPtr)
+ then moduleError >>= \ err -> ioError (userError ("dlopen: " ++ err))
+ else return $ Module modPtr
diff --git a/System/Posix/DynamicLinker/Prim.hsc b/System/Posix/DynamicLinker/Prim.hsc
index 2e5409e..9a21d77 100644
--- a/System/Posix/DynamicLinker/Prim.hsc
+++ b/System/Posix/DynamicLinker/Prim.hsc
@@ -30,7 +30,7 @@ module System.Posix.DynamicLinker.Prim (
packRTLDFlags,
RTLDFlags(..),
packDL,
- DL(..)
+ DL(..),
)
where