{-# LINE 1 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LINE 2 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LANGUAGE Trustworthy #-}
{-# LINE 4 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# OPTIONS_GHC -fno-warn-trustworthy-safe #-}
{-# LINE 6 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LINE 7 "System/Posix/DynamicLinker/Prim.hsc" #-}
module System.Posix.DynamicLinker.Prim (
c_dlopen,
c_dlsym,
c_dlerror,
c_dlclose,
haveRtldNext,
haveRtldLocal,
packRTLDFlags,
RTLDFlags(..),
packDL,
DL(..),
)
where
{-# LINE 41 "System/Posix/DynamicLinker/Prim.hsc" #-}
import Data.Bits ( (.|.) )
import Foreign.Ptr ( Ptr, FunPtr, nullPtr )
import Foreign.C.Types
import Foreign.C.String ( CString )
haveRtldNext :: Bool
{-# LINE 64 "System/Posix/DynamicLinker/Prim.hsc" #-}
haveRtldNext = False
{-# LINE 66 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LINE 70 "System/Posix/DynamicLinker/Prim.hsc" #-}
haveRtldLocal :: Bool
haveRtldLocal = True
{-# DEPRECATED haveRtldLocal "defaults to True" #-}
data RTLDFlags
= RTLD_LAZY
| RTLD_NOW
| RTLD_GLOBAL
| RTLD_LOCAL
deriving (Show, Read)
foreign import ccall unsafe "dlopen" c_dlopen :: CString -> CInt -> IO (Ptr ())
foreign import ccall unsafe "dlsym" c_dlsym :: Ptr () -> CString -> IO (FunPtr a)
foreign import ccall unsafe "dlerror" c_dlerror :: IO CString
foreign import ccall unsafe "dlclose" c_dlclose :: (Ptr ()) -> IO CInt
packRTLDFlags :: [RTLDFlags] -> CInt
packRTLDFlags flags = foldl (\ s f -> (packRTLDFlag f) .|. s) 0 flags
packRTLDFlag :: RTLDFlags -> CInt
packRTLDFlag RTLD_LAZY = 1
{-# LINE 95 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_NOW = 2
{-# LINE 96 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_GLOBAL = 256
{-# LINE 97 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_LOCAL = 0
{-# LINE 98 "System/Posix/DynamicLinker/Prim.hsc" #-}
data DL = Null | Next | Default | DLHandle (Ptr ()) deriving (Show)
packDL :: DL -> Ptr ()
packDL Null = nullPtr
{-# LINE 115 "System/Posix/DynamicLinker/Prim.hsc" #-}
packDL Next = error "RTLD_NEXT not available"
{-# LINE 117 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LINE 121 "System/Posix/DynamicLinker/Prim.hsc" #-}
packDL Default = nullPtr
{-# LINE 123 "System/Posix/DynamicLinker/Prim.hsc" #-}
packDL (DLHandle h) = h