X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FForeignPtr.hs;h=bb74f0b1d652b6b410fd9d5e017bd8d022443f30;hb=4b26136ab82fb1ff12e49477c4833a9586d368c5;hp=f6a61c1c070cfeb22232cf5fad91bdcc1a9f9e58;hpb=0d6c1599c246100deb2fa54315811ed94d1a300c;p=haskell-directory.git diff --git a/GHC/ForeignPtr.hs b/GHC/ForeignPtr.hs index f6a61c1..bb74f0b 100644 --- a/GHC/ForeignPtr.hs +++ b/GHC/ForeignPtr.hs @@ -13,13 +13,16 @@ -- ----------------------------------------------------------------------------- +-- #hide module GHC.ForeignPtr ( ForeignPtr(..), FinalizerPtr, newForeignPtr_, mallocForeignPtr, + mallocPlainForeignPtr, mallocForeignPtrBytes, + mallocPlainForeignPtrBytes, addForeignPtrFinalizer, touchForeignPtr, unsafeForeignPtrToPtr, @@ -30,15 +33,17 @@ module GHC.ForeignPtr ) where import Control.Monad ( sequence_ ) -import Foreign.Ptr import Foreign.Storable +import Numeric ( showHex ) -import GHC.List ( null ) +import GHC.Show +import GHC.Num +import GHC.List ( null, replicate, length ) import GHC.Base import GHC.IOBase -import GHC.Ptr ( Ptr(..) ) +import GHC.STRef ( STRef(..) ) +import GHC.Ptr ( Ptr(..), FunPtr, castFunPtrToPtr ) import GHC.Err -import GHC.Show -- |The type 'ForeignPtr' represents references to objects that are -- maintained in a foreign language, i.e., that are not part of the @@ -56,9 +61,21 @@ import GHC.Show -- type argument of 'ForeignPtr' should normally be an instance of -- class 'Storable'. -- -data ForeignPtr a - = ForeignPtr ForeignObj# !(IORef [IO ()]) - | MallocPtr (MutableByteArray# RealWorld) !(IORef [IO ()]) +data ForeignPtr a = ForeignPtr Addr# ForeignPtrContents + -- we cache the Addr# in the ForeignPtr object, but attach + -- the finalizer to the IORef (or the MutableByteArray# in + -- the case of a MallocPtr). The aim of the representation + -- is to make withForeignPtr efficient; in fact, withForeignPtr + -- should be just as efficient as unpacking a Ptr, and multiple + -- withForeignPtrs can share an unpacked ForeignPtr. Note + -- that touchForeignPtr only has to touch the ForeignPtrContents + -- object, because that ensures that whatever the finalizer is + -- attached to is kept alive. + +data ForeignPtrContents + = PlainForeignPtr !(IORef [IO ()]) + | MallocPtr (MutableByteArray# RealWorld) !(IORef [IO ()]) + | PlainPtr (MutableByteArray# RealWorld) instance Eq (ForeignPtr a) where p == q = unsafeForeignPtrToPtr p == unsafeForeignPtrToPtr q @@ -69,6 +86,7 @@ instance Ord (ForeignPtr a) where instance Show (ForeignPtr a) where showsPrec p f = showsPrec p (unsafeForeignPtrToPtr f) + -- |A Finalizer is represented as a pointer to a foreign function that, at -- finalisation time, gets as an argument a plain pointer variant of the -- foreign pointer that the finalizer is associated with. @@ -85,6 +103,13 @@ newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a) -- in fact there is no guarantee that the finalizer will eventually -- run at all. -- +-- Note that references from a finalizer do not necessarily prevent +-- another object from being finalized. If A's finalizer refers to B +-- (perhaps using 'touchForeignPtr', then the only guarantee is that +-- B's finalizer will never be started before A's. If both A and B +-- are unreachable, then both finalizers will start together. See +-- 'touchForeignPtr' for more on finalizer ordering. +-- newConcForeignPtr p finalizer = do fObj <- newForeignPtr_ p addForeignPtrConcFinalizer fObj finalizer @@ -101,13 +126,22 @@ mallocForeignPtr :: Storable a => IO (ForeignPtr a) -- although it may be implemented differently internally: you may not -- assume that the memory returned by 'mallocForeignPtr' has been -- allocated with 'Foreign.Marshal.Alloc.malloc'. +-- +-- GHC notes: 'mallocForeignPtr' has a heavily optimised +-- implementation in GHC. It uses pinned memory in the garbage +-- collected heap, so the 'ForeignPtr' does not require a finalizer to +-- free the memory. Use of 'mallocForeignPtr' and associated +-- functions is strongly recommended in preference to 'newForeignPtr' +-- with a finalizer. +-- mallocForeignPtr = doMalloc undefined where doMalloc :: Storable b => b -> IO (ForeignPtr b) doMalloc a = do r <- newIORef [] IO $ \s -> case newPinnedByteArray# size s of { (# s, mbarr# #) -> - (# s, MallocPtr mbarr# r #) + (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#)) + (MallocPtr mbarr# r) #) } where (I# size) = sizeOf a @@ -118,7 +152,42 @@ mallocForeignPtrBytes (I# size) = do r <- newIORef [] IO $ \s -> case newPinnedByteArray# size s of { (# s, mbarr# #) -> - (# s, MallocPtr mbarr# r #) + (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#)) + (MallocPtr mbarr# r) #) + } + +-- | Allocate some memory and return a 'ForeignPtr' to it. The memory +-- will be released automatically when the 'ForeignPtr' is discarded. +-- +-- GHC notes: 'mallocPlainForeignPtr' has a heavily optimised +-- implementation in GHC. It uses pinned memory in the garbage +-- collected heap, as for mallocForeignPtr. Unlike mallocForeignPtr, a +-- ForeignPtr created with mallocPlainForeignPtr carries no finalizers. +-- It is not possible to add a finalizer to a ForeignPtr created with +-- mallocPlainForeignPtr. This is useful for ForeignPtrs that will live +-- only inside Haskell (such as those created for packed strings). +-- Attempts to add a finalizer to a ForeignPtr created this way, or to +-- finalize such a pointer, will throw an exception. +-- +mallocPlainForeignPtr :: Storable a => IO (ForeignPtr a) +mallocPlainForeignPtr = doMalloc undefined + where doMalloc :: Storable b => b -> IO (ForeignPtr b) + doMalloc a = IO $ \s -> + case newPinnedByteArray# size s of { (# s, mbarr# #) -> + (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#)) + (PlainPtr mbarr#) #) + } + where (I# size) = sizeOf a + +-- | This function is similar to 'mallocForeignPtrBytes', except that +-- the internally an optimised ForeignPtr representation with no +-- finalizer is used. Attempts to add a finalizer will cause an +-- exception to be thrown. +mallocPlainForeignPtrBytes :: Int -> IO (ForeignPtr a) +mallocPlainForeignPtrBytes (I# size) = IO $ \s -> + case newPinnedByteArray# size s of { (# s, mbarr# #) -> + (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#)) + (PlainPtr mbarr#) #) } addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO () @@ -144,45 +213,42 @@ addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO () -- are finalized objects, so a finalizer should not refer to a 'Handle' -- (including @stdout@, @stdin@ or @stderr@). -- -addForeignPtrConcFinalizer f@(ForeignPtr fo r) finalizer = do +addForeignPtrConcFinalizer (ForeignPtr a c) finalizer = + addForeignPtrConcFinalizer_ c finalizer + +addForeignPtrConcFinalizer_ f@(PlainForeignPtr r) finalizer = do fs <- readIORef r writeIORef r (finalizer : fs) if (null fs) then IO $ \s -> - let p = unsafeForeignPtrToPtr f in - case mkWeak# fo () (foreignPtrFinalizer r p) s of - (# s1, w #) -> (# s1, () #) + case r of { IORef (STRef r#) -> + case mkWeak# r# () (foreignPtrFinalizer r) s of { (# s1, w #) -> + (# s1, () #) }} else return () -addForeignPtrConcFinalizer f@(MallocPtr fo r) finalizer = do +addForeignPtrConcFinalizer_ f@(MallocPtr fo r) finalizer = do fs <- readIORef r writeIORef r (finalizer : fs) if (null fs) then IO $ \s -> - let p = unsafeForeignPtrToPtr f in - case mkWeak# fo () (do foreignPtrFinalizer r p - touchPinnedByteArray# fo) s of + case mkWeak# fo () (do foreignPtrFinalizer r; touch f) s of (# s1, w #) -> (# s1, () #) else return () +addForeignPtrConcFinalizer_ _ _ = + error "GHC.ForeignPtr: attempt to add a finalizer to plain pointer" + foreign import ccall "dynamic" mkFinalizer :: FinalizerPtr a -> Ptr a -> IO () -foreignPtrFinalizer :: IORef [IO ()] -> Ptr a -> IO () -foreignPtrFinalizer r p = do - fs <- readIORef r - sequence_ fs +foreignPtrFinalizer :: IORef [IO ()] -> IO () +foreignPtrFinalizer r = do fs <- readIORef r; sequence_ fs newForeignPtr_ :: Ptr a -> IO (ForeignPtr a) -- ^Turns a plain memory reference into a foreign pointer that may be -- associated with finalizers by using 'addForeignPtrFinalizer'. newForeignPtr_ (Ptr obj) = do r <- newIORef [] - IO $ \ s# -> - case mkForeignObj# obj s# of - (# s1#, fo# #) -> (# s1#, ForeignPtr fo# r #) - -touchPinnedByteArray# :: MutableByteArray# RealWorld -> IO () -touchPinnedByteArray# ba# = IO $ \s -> case touch# ba# s of s -> (# s, () #) + return (ForeignPtr obj (PlainForeignPtr r)) touchForeignPtr :: ForeignPtr a -> IO () -- ^This function ensures that the foreign object in @@ -191,8 +257,8 @@ touchForeignPtr :: ForeignPtr a -> IO () -- does a 'touchForeignPtr' after it -- executes the user action. -- --- Note that this function should not be used to express liveness --- dependencies between 'ForeignPtr's. For example, if the finalizer +-- Note that this function should not be used to express dependencies +-- between finalizers on 'ForeignPtr's. For example, if the finalizer -- for a 'ForeignPtr' @F1@ calls 'touchForeignPtr' on a second -- 'ForeignPtr' @F2@, then the only guarantee is that the finalizer -- for @F2@ is never started before the finalizer for @F1@. They @@ -206,12 +272,12 @@ touchForeignPtr :: ForeignPtr a -> IO () -- between the finalizers, but even then the runtime sometimes runs -- multiple finalizers sequentially in a single thread (for -- performance reasons), so synchronisation between finalizers could --- result in artificial deadlock. +-- result in artificial deadlock. Another alternative is to use +-- explicit reference counting. -- -touchForeignPtr (ForeignPtr fo r) - = IO $ \s -> case touch# fo s of s -> (# s, () #) -touchForeignPtr (MallocPtr fo r) - = touchPinnedByteArray# fo +touchForeignPtr (ForeignPtr fo r) = touch r + +touch r = IO $ \s -> case touch# r s of s -> (# s, () #) unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a -- ^This function extracts the pointer component of a foreign @@ -228,22 +294,23 @@ unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a -- than combinations of 'unsafeForeignPtrToPtr' and -- 'touchForeignPtr'. However, the later routines -- are occasionally preferred in tool generated marshalling code. -unsafeForeignPtrToPtr (ForeignPtr fo r) = Ptr (foreignObjToAddr# fo) -unsafeForeignPtrToPtr (MallocPtr fo r) = Ptr (byteArrayContents# (unsafeCoerce# fo)) +unsafeForeignPtrToPtr (ForeignPtr fo r) = Ptr fo castForeignPtr :: ForeignPtr a -> ForeignPtr b -- ^This function casts a 'ForeignPtr' -- parameterised by one type into another type. castForeignPtr f = unsafeCoerce# f --- | Causes a the finalizers associated with a foreign pointer to be run +-- | Causes the finalizers associated with a foreign pointer to be run -- immediately. finalizeForeignPtr :: ForeignPtr a -> IO () -finalizeForeignPtr foreignPtr = do +finalizeForeignPtr (ForeignPtr _ (PlainPtr _)) = return () -- no effect +finalizeForeignPtr (ForeignPtr _ foreignPtr) = do finalizers <- readIORef refFinalizers sequence_ finalizers writeIORef refFinalizers [] where refFinalizers = case foreignPtr of - (ForeignPtr _ ref) -> ref - (MallocPtr _ ref) -> ref + (PlainForeignPtr ref) -> ref + (MallocPtr _ ref) -> ref +