{-# LINE 1 "System/Posix/DynamicLinker/Prim.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE Trustworthy #-}{-# OPTIONS_GHC -Wno-trustworthy-safe #-}------------------------------------------------------------------------------- |-- 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.-------------------------------------------------------------------------------moduleSystem.Posix.DynamicLinker.Prim(-- * low level APIc_dlopen ,c_dlsym ,c_dlerror ,c_dlclose ,-- dlAddr, -- XXX NYIhaveRtldNext ,haveRtldLocal ,packRTLDFlags ,RTLDFlags (..),packDL ,DL (..),)whereimportData.Bits((.|.))importForeign.Ptr(Ptr,FunPtr,nullPtr)importForeign.C.TypesimportForeign.C.String(CString){-# LINE 50 "System/Posix/DynamicLinker/Prim.hsc" #-}-- |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 whether 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 64 "System/Posix/DynamicLinker/Prim.hsc" #-}haveRtldNext=Trueforeignimportccallunsafe"__hsunix_rtldNext"rtldNext ::Ptra {-# LINE 69 "System/Posix/DynamicLinker/Prim.hsc" #-}{-# LINE 71 "System/Posix/DynamicLinker/Prim.hsc" #-}foreignimportccallunsafe"__hsunix_rtldDefault"rtldDefault::Ptra{-# LINE 73 "System/Posix/DynamicLinker/Prim.hsc" #-}haveRtldLocal ::BoolhaveRtldLocal :: Bool
haveRtldLocal =Bool
True{-# DEPRECATEDhaveRtldLocal"defaults to True"#-}-- |Flags for 'System.Posix.DynamicLinker.dlopen'.dataRTLDFlags =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
$cshowsPrec :: Int -> RTLDFlags -> ShowS
showsPrec :: Int -> RTLDFlags -> ShowS
$cshow :: RTLDFlags -> String
show :: RTLDFlags -> String
$cshowList :: [RTLDFlags] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS RTLDFlags
readsPrec :: Int -> ReadS RTLDFlags
$creadList :: ReadS [RTLDFlags]
readList :: ReadS [RTLDFlags]
$creadPrec :: ReadPrec RTLDFlags
readPrec :: ReadPrec RTLDFlags
$creadListPrec :: ReadPrec [RTLDFlags]
readListPrec :: ReadPrec [RTLDFlags]
Read){-# LINE 89 "System/Posix/DynamicLinker/Prim.hsc" #-}foreignimportcapisafe"dlfcn.h dlopen"c_dlopen::CString->CInt->IO(Ptr())foreignimportcapiunsafe"dlfcn.h dlsym"c_dlsym ::Ptr()->CString->IO(FunPtra )foreignimportcapiunsafe"dlfcn.h dlerror"c_dlerror ::IOCStringforeignimportcapisafe"dlfcn.h dlclose"c_dlclose ::(Ptr())->IOCInt{-# LINE 99 "System/Posix/DynamicLinker/Prim.hsc" #-}packRTLDFlags ::[RTLDFlags ]->CIntpackRTLDFlags :: [RTLDFlags] -> CInt
packRTLDFlags [RTLDFlags]
flags =(CInt -> RTLDFlags -> CInt) -> CInt -> [RTLDFlags] -> CInt
forall b a. (b -> a -> b) -> b -> [a] -> b
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{-# LINE 105 "System/Posix/DynamicLinker/Prim.hsc" #-}packRTLDFlag :: RTLDFlags -> CInt
packRTLDFlag RTLDFlags
RTLD_LAZY =CInt
1{-# LINE 107 "System/Posix/DynamicLinker/Prim.hsc" #-}packRTLDFlagRTLD_NOW=2{-# LINE 108 "System/Posix/DynamicLinker/Prim.hsc" #-}packRTLDFlagRTLD_GLOBAL=256{-# LINE 109 "System/Posix/DynamicLinker/Prim.hsc" #-}packRTLDFlagRTLD_LOCAL=0{-# LINE 110 "System/Posix/DynamicLinker/Prim.hsc" #-}{-# LINE 118 "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'.dataDL =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
$cshowsPrec :: Int -> DL -> ShowS
showsPrec :: Int -> DL -> ShowS
$cshow :: DL -> String
show :: DL -> String
$cshowList :: [DL] -> ShowS
showList :: [DL] -> ShowS
Show)packDL ::DL ->Ptr()packDL :: DL -> Ptr ()
packDL DL
Null =Ptr ()
forall a. Ptr a
nullPtr{-# LINE 132 "System/Posix/DynamicLinker/Prim.hsc" #-}packDLNext=rtldNext{-# LINE 136 "System/Posix/DynamicLinker/Prim.hsc" #-}{-# LINE 138 "System/Posix/DynamicLinker/Prim.hsc" #-}packDLDefault=rtldDefault{-# LINE 142 "System/Posix/DynamicLinker/Prim.hsc" #-}packDL (DLHandle Ptr ()
h )=Ptr ()
h 

AltStyle によって変換されたページ (->オリジナル) /