{-# LINE 1 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
{-# LANGUAGE Trustworthy #-}

{-# LINE 3 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
{-# OPTIONS_GHC -fno-warn-trustworthy-safe #-}

{-# LINE 5 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.DynamicLinker.Prim
-- 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(3)@ and friends
--  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.Prim (
  -- * low level API
  c_dlopen,
  c_dlsym,
  c_dlerror,
  c_dlclose,
  -- dlAddr, -- XXX NYI
  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 )


-- |On some hosts (e.g. SuSe and Ubuntu Linux) @RTLD_NEXT@ (and
-- @RTLD_DEFAULT@) are not visible without setting the macro
-- @_GNU_SOURCE@. Since we don\'t want to define this macro, you can use
-- the function 'haveRtldNext' to check wether the flag `Next` is
-- available. Ideally, this will be optimized by the compiler so that it
-- should be as efficient as an @#ifdef@.
--
-- If you fail to test the flag and use it although it is undefined,
-- 'packDL' will throw an error.

haveRtldNext :: Bool


{-# LINE 60 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
haveRtldNext = True
foreign import ccall unsafe "__hsunix_rtldNext" rtldNext :: Ptr a

{-# LINE 65 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}


{-# LINE 67 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
foreign import ccall unsafe "__hsunix_rtldDefault" rtldDefault :: Ptr a

{-# LINE 69 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}

haveRtldLocal :: Bool
haveRtldLocal :: Bool
haveRtldLocal = Bool
True
{-# DEPRECATED haveRtldLocal "defaults to True" #-}


-- |Flags for 'System.Posix.DynamicLinker.dlopen'.

data RTLDFlags
  = RTLD_LAZY
  | RTLD_NOW
  | RTLD_GLOBAL
  | RTLD_LOCAL
    deriving (Int -> RTLDFlags -> ShowS
[RTLDFlags] -> ShowS
RTLDFlags -> String
(Int -> RTLDFlags -> ShowS)
-> (RTLDFlags -> String)
-> ([RTLDFlags] -> ShowS)
-> Show RTLDFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTLDFlags] -> ShowS
$cshowList :: [RTLDFlags] -> ShowS
show :: RTLDFlags -> String
$cshow :: RTLDFlags -> String
showsPrec :: Int -> RTLDFlags -> ShowS
$cshowsPrec :: Int -> RTLDFlags -> ShowS
Show, ReadPrec [RTLDFlags]
ReadPrec RTLDFlags
Int -> ReadS RTLDFlags
ReadS [RTLDFlags]
(Int -> ReadS RTLDFlags)
-> ReadS [RTLDFlags]
-> ReadPrec RTLDFlags
-> ReadPrec [RTLDFlags]
-> Read RTLDFlags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTLDFlags]
$creadListPrec :: ReadPrec [RTLDFlags]
readPrec :: ReadPrec RTLDFlags
$creadPrec :: ReadPrec RTLDFlags
readList :: ReadS [RTLDFlags]
$creadList :: ReadS [RTLDFlags]
readsPrec :: Int -> ReadS RTLDFlags
$creadsPrec :: Int -> ReadS RTLDFlags
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 :: [RTLDFlags] -> CInt
packRTLDFlags [RTLDFlags]
flags = (CInt -> RTLDFlags -> CInt) -> CInt -> [RTLDFlags] -> CInt
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\ CInt
s RTLDFlags
f -> (RTLDFlags -> CInt
packRTLDFlag RTLDFlags
f) CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.|. CInt
s) CInt
0 [RTLDFlags]
flags

packRTLDFlag :: RTLDFlags -> CInt
packRTLDFlag :: RTLDFlags -> CInt
packRTLDFlag RTLDFlags
RTLD_LAZY = CInt
1
{-# LINE 94 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_NOW = 2
{-# LINE 95 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_GLOBAL = 256
{-# LINE 96 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
packRTLDFlag RTLD_LOCAL = 0
{-# LINE 97 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}


-- |Flags for 'System.Posix.DynamicLinker.dlsym'. Notice that 'Next'
-- might not be available on your particular platform! Use
-- 'haveRtldNext'.
--
-- If 'RTLD_DEFAULT' is not defined on your platform, 'packDL' 'Default'
-- reduces to 'nullPtr'.

data DL = Null | Next | Default | DLHandle (Ptr ()) deriving (Int -> DL -> ShowS
[DL] -> ShowS
DL -> String
(Int -> DL -> ShowS)
-> (DL -> String) -> ([DL] -> ShowS) -> Show DL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DL] -> ShowS
$cshowList :: [DL] -> ShowS
show :: DL -> String
$cshow :: DL -> String
showsPrec :: Int -> DL -> ShowS
$cshowsPrec :: Int -> DL -> ShowS
Show)

packDL :: DL -> Ptr ()
packDL :: DL -> Ptr ()
packDL DL
Null = Ptr ()
forall a. Ptr a
nullPtr


{-# LINE 112 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
packDL Next = rtldNext

{-# LINE 116 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}


{-# LINE 118 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}
packDL Default = rtldDefault

{-# LINE 122 "libraries/unix/System/Posix/DynamicLinker/Prim.hsc" #-}

packDL (DLHandle Ptr ()
h) = Ptr ()
h