{-# LINE 1 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE Trustworthy #-}
{-# OPTIONS_GHC -Wno-trustworthy-safe #-}
module System.Posix.DynamicLinker.Prim (
c_dlopen,
c_dlsym,
c_dlerror,
c_dlclose,
haveRtldNext,
haveRtldLocal,
packRTLDFlags,
RTLDFlags(..),
packDL,
DL(..),
)
where
import Data.Bits ( (.|.) )
import Foreign.Ptr ( Ptr, FunPtr, nullPtr )
import Foreign.C.Types
import Foreign.C.String ( CString )
{-# LINE 50 "System/Posix/DynamicLinker/Prim.hsc" #-}
haveRtldNext :: Bool
{-# LINE 64 "System/Posix/DynamicLinker/Prim.hsc" #-}
haveRtldNext = True
foreign import ccall unsafe "__hsunix_rtldNext" rtldNext :: Ptr a
{-# LINE 69 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LINE 71 "System/Posix/DynamicLinker/Prim.hsc" #-}
foreign import ccall unsafe "__hsunix_rtldDefault" rtldDefault :: Ptr a
{-# LINE 73 "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)
{-# LINE 89 "System/Posix/DynamicLinker/Prim.hsc" #-}
foreign import capi safe "dlfcn.h dlopen" c_dlopen :: CString -> CInt -> IO (Ptr ())
foreign import capi unsafe "dlfcn.h dlsym" c_dlsym :: Ptr () -> CString -> IO (FunPtr a)
foreign import capi unsafe "dlfcn.h dlerror" c_dlerror :: IO CString
foreign import capi safe "dlfcn.h dlclose" c_dlclose :: (Ptr ()) -> IO CInt
{-# LINE 99 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlags :: [RTLDFlags] -> CInt
packRTLDFlags flags = foldl (\ s f -> (packRTLDFlag f) .|. s) 0 flags
packRTLDFlag :: RTLDFlags -> CInt
{-# LINE 105 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_LAZY = 1
{-# LINE 107 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_NOW = 2
{-# LINE 108 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_GLOBAL = 256
{-# LINE 109 "System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_LOCAL = 0
{-# LINE 110 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LINE 118 "System/Posix/DynamicLinker/Prim.hsc" #-}
data DL = Null | Next | Default | DLHandle (Ptr ()) deriving (Show)
packDL :: DL -> Ptr ()
packDL Null = nullPtr
{-# LINE 132 "System/Posix/DynamicLinker/Prim.hsc" #-}
packDL Next = rtldNext
{-# LINE 136 "System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LINE 138 "System/Posix/DynamicLinker/Prim.hsc" #-}
packDL Default = rtldDefault
{-# LINE 142 "System/Posix/DynamicLinker/Prim.hsc" #-}
packDL (DLHandle h) = h