2e737f0fa36263e69a7719aa30d9d83562478304
[ghc-base.git] / GHC / ForeignPtr.hs
1 {-# LANGUAGE CPP
2            , NoImplicitPrelude
3            , BangPatterns
4            , MagicHash
5            , UnboxedTuples
6   #-}
7 {-# OPTIONS_HADDOCK hide #-}
8
9 -----------------------------------------------------------------------------
10 -- |
11 -- Module      :  GHC.ForeignPtr
12 -- Copyright   :  (c) The University of Glasgow, 1992-2003
13 -- License     :  see libraries/base/LICENSE
14 -- 
15 -- Maintainer  :  cvs-ghc@haskell.org
16 -- Stability   :  internal
17 -- Portability :  non-portable (GHC extensions)
18 --
19 -- GHC's implementation of the 'ForeignPtr' data type.
20 -- 
21 -----------------------------------------------------------------------------
22
23 -- #hide
24 module GHC.ForeignPtr
25   (
26         ForeignPtr(..),
27         FinalizerPtr,
28         FinalizerEnvPtr,
29         newForeignPtr_,
30         mallocForeignPtr,
31         mallocPlainForeignPtr,
32         mallocForeignPtrBytes,
33         mallocPlainForeignPtrBytes,
34         addForeignPtrFinalizer,
35         addForeignPtrFinalizerEnv,
36         touchForeignPtr,
37         unsafeForeignPtrToPtr,
38         castForeignPtr,
39         newConcForeignPtr,
40         addForeignPtrConcFinalizer,
41         finalizeForeignPtr
42   ) where
43
44 import Control.Monad    ( sequence_ )
45 import Foreign.Storable
46 import Data.Typeable
47
48 import GHC.Show
49 import GHC.List         ( null )
50 import GHC.Base
51 import GHC.IORef
52 import GHC.STRef        ( STRef(..) )
53 import GHC.Ptr          ( Ptr(..), FunPtr(..) )
54 import GHC.Err
55
56 #include "Typeable.h"
57
58 -- |The type 'ForeignPtr' represents references to objects that are
59 -- maintained in a foreign language, i.e., that are not part of the
60 -- data structures usually managed by the Haskell storage manager.
61 -- The essential difference between 'ForeignPtr's and vanilla memory
62 -- references of type @Ptr a@ is that the former may be associated
63 -- with /finalizers/. A finalizer is a routine that is invoked when
64 -- the Haskell storage manager detects that - within the Haskell heap
65 -- and stack - there are no more references left that are pointing to
66 -- the 'ForeignPtr'.  Typically, the finalizer will, then, invoke
67 -- routines in the foreign language that free the resources bound by
68 -- the foreign object.
69 --
70 -- The 'ForeignPtr' is parameterised in the same way as 'Ptr'.  The
71 -- type argument of 'ForeignPtr' should normally be an instance of
72 -- class 'Storable'.
73 --
74 data ForeignPtr a = ForeignPtr Addr# ForeignPtrContents
75         -- we cache the Addr# in the ForeignPtr object, but attach
76         -- the finalizer to the IORef (or the MutableByteArray# in
77         -- the case of a MallocPtr).  The aim of the representation
78         -- is to make withForeignPtr efficient; in fact, withForeignPtr
79         -- should be just as efficient as unpacking a Ptr, and multiple
80         -- withForeignPtrs can share an unpacked ForeignPtr.  Note
81         -- that touchForeignPtr only has to touch the ForeignPtrContents
82         -- object, because that ensures that whatever the finalizer is
83         -- attached to is kept alive.
84
85 INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr")
86
87 data Finalizers
88   = NoFinalizers
89   | CFinalizers
90   | HaskellFinalizers
91     deriving Eq
92
93 data ForeignPtrContents
94   = PlainForeignPtr !(IORef (Finalizers, [IO ()]))
95   | MallocPtr      (MutableByteArray# RealWorld) !(IORef (Finalizers, [IO ()]))
96   | PlainPtr       (MutableByteArray# RealWorld)
97
98 instance Eq (ForeignPtr a) where
99     p == q  =  unsafeForeignPtrToPtr p == unsafeForeignPtrToPtr q
100
101 instance Ord (ForeignPtr a) where
102     compare p q  =  compare (unsafeForeignPtrToPtr p) (unsafeForeignPtrToPtr q)
103
104 instance Show (ForeignPtr a) where
105     showsPrec p f = showsPrec p (unsafeForeignPtrToPtr f)
106
107
108 -- |A finalizer is represented as a pointer to a foreign function that, at
109 -- finalisation time, gets as an argument a plain pointer variant of the
110 -- foreign pointer that the finalizer is associated with.
111 -- 
112 type FinalizerPtr a        = FunPtr (Ptr a -> IO ())
113 type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ())
114
115 newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
116 --
117 -- ^Turns a plain memory reference into a foreign object by
118 -- associating a finalizer - given by the monadic operation - with the
119 -- reference.  The storage manager will start the finalizer, in a
120 -- separate thread, some time after the last reference to the
121 -- @ForeignPtr@ is dropped.  There is no guarantee of promptness, and
122 -- in fact there is no guarantee that the finalizer will eventually
123 -- run at all.
124 --
125 -- Note that references from a finalizer do not necessarily prevent
126 -- another object from being finalized.  If A's finalizer refers to B
127 -- (perhaps using 'touchForeignPtr', then the only guarantee is that
128 -- B's finalizer will never be started before A's.  If both A and B
129 -- are unreachable, then both finalizers will start together.  See
130 -- 'touchForeignPtr' for more on finalizer ordering.
131 --
132 newConcForeignPtr p finalizer
133   = do fObj <- newForeignPtr_ p
134        addForeignPtrConcFinalizer fObj finalizer
135        return fObj
136
137 mallocForeignPtr :: Storable a => IO (ForeignPtr a)
138 -- ^ Allocate some memory and return a 'ForeignPtr' to it.  The memory
139 -- will be released automatically when the 'ForeignPtr' is discarded.
140 --
141 -- 'mallocForeignPtr' is equivalent to
142 --
143 -- >    do { p <- malloc; newForeignPtr finalizerFree p }
144 -- 
145 -- although it may be implemented differently internally: you may not
146 -- assume that the memory returned by 'mallocForeignPtr' has been
147 -- allocated with 'Foreign.Marshal.Alloc.malloc'.
148 --
149 -- GHC notes: 'mallocForeignPtr' has a heavily optimised
150 -- implementation in GHC.  It uses pinned memory in the garbage
151 -- collected heap, so the 'ForeignPtr' does not require a finalizer to
152 -- free the memory.  Use of 'mallocForeignPtr' and associated
153 -- functions is strongly recommended in preference to 'newForeignPtr'
154 -- with a finalizer.
155 -- 
156 mallocForeignPtr = doMalloc undefined
157   where doMalloc :: Storable b => b -> IO (ForeignPtr b)
158         doMalloc a
159           | I# size < 0 = error "mallocForeignPtr: size must be >= 0"
160           | otherwise = do
161           r <- newIORef (NoFinalizers, [])
162           IO $ \s ->
163             case newAlignedPinnedByteArray# size align s of { (# s', mbarr# #) ->
164              (# s', ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
165                                (MallocPtr mbarr# r) #)
166             }
167             where !(I# size)  = sizeOf a
168                   !(I# align) = alignment a
169
170 -- | This function is similar to 'mallocForeignPtr', except that the
171 -- size of the memory required is given explicitly as a number of bytes.
172 mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
173 mallocForeignPtrBytes size | size < 0 =
174   error "mallocForeignPtrBytes: size must be >= 0"
175 mallocForeignPtrBytes (I# size) = do 
176   r <- newIORef (NoFinalizers, [])
177   IO $ \s ->
178      case newPinnedByteArray# size s      of { (# s', mbarr# #) ->
179        (# s', ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
180                          (MallocPtr mbarr# r) #)
181      }
182
183 -- | Allocate some memory and return a 'ForeignPtr' to it.  The memory
184 -- will be released automatically when the 'ForeignPtr' is discarded.
185 --
186 -- GHC notes: 'mallocPlainForeignPtr' has a heavily optimised
187 -- implementation in GHC.  It uses pinned memory in the garbage
188 -- collected heap, as for mallocForeignPtr. Unlike mallocForeignPtr, a
189 -- ForeignPtr created with mallocPlainForeignPtr carries no finalizers.
190 -- It is not possible to add a finalizer to a ForeignPtr created with
191 -- mallocPlainForeignPtr. This is useful for ForeignPtrs that will live
192 -- only inside Haskell (such as those created for packed strings).
193 -- Attempts to add a finalizer to a ForeignPtr created this way, or to
194 -- finalize such a pointer, will throw an exception.
195 -- 
196 mallocPlainForeignPtr :: Storable a => IO (ForeignPtr a)
197 mallocPlainForeignPtr = doMalloc undefined
198   where doMalloc :: Storable b => b -> IO (ForeignPtr b)
199         doMalloc a
200           | I# size < 0 = error "mallocForeignPtr: size must be >= 0"
201           | otherwise = IO $ \s ->
202             case newAlignedPinnedByteArray# size align s of { (# s', mbarr# #) ->
203              (# s', ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
204                                (PlainPtr mbarr#) #)
205             }
206             where !(I# size)  = sizeOf a
207                   !(I# align) = alignment a
208
209 -- | This function is similar to 'mallocForeignPtrBytes', except that
210 -- the internally an optimised ForeignPtr representation with no
211 -- finalizer is used. Attempts to add a finalizer will cause an
212 -- exception to be thrown.
213 mallocPlainForeignPtrBytes :: Int -> IO (ForeignPtr a)
214 mallocPlainForeignPtrBytes size | size < 0 =
215   error "mallocPlainForeignPtrBytes: size must be >= 0"
216 mallocPlainForeignPtrBytes (I# size) = IO $ \s ->
217     case newPinnedByteArray# size s      of { (# s', mbarr# #) ->
218        (# s', ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
219                          (PlainPtr mbarr#) #)
220      }
221
222 addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()
223 -- ^This function adds a finalizer to the given foreign object.  The
224 -- finalizer will run /before/ all other finalizers for the same
225 -- object which have already been registered.
226 addForeignPtrFinalizer (FunPtr fp) (ForeignPtr p c) = case c of
227   PlainForeignPtr r -> f r >> return ()
228   MallocPtr     _ r -> f r >> return ()
229   _ -> error "GHC.ForeignPtr: attempt to add a finalizer to a plain pointer"
230  where
231     f r =
232       noMixing CFinalizers r $
233         IO $ \s ->
234           case r of { IORef (STRef r#) ->
235           case mkWeakForeignEnv# r# () fp p 0# nullAddr# s of { (# s1, w #) ->
236           (# s1, finalizeForeign w #) }}
237
238 addForeignPtrFinalizerEnv ::
239   FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO ()
240 -- ^ Like 'addForeignPtrFinalizerEnv' but allows the finalizer to be
241 -- passed an additional environment parameter to be passed to the
242 -- finalizer.  The environment passed to the finalizer is fixed by the
243 -- second argument to 'addForeignPtrFinalizerEnv'
244 addForeignPtrFinalizerEnv (FunPtr fp) (Ptr ep) (ForeignPtr p c) = case c of
245   PlainForeignPtr r -> f r >> return ()
246   MallocPtr     _ r -> f r >> return ()
247   _ -> error "GHC.ForeignPtr: attempt to add a finalizer to a plain pointer"
248  where
249     f r =
250       noMixing CFinalizers r $
251         IO $ \s ->
252           case r of { IORef (STRef r#) ->
253           case mkWeakForeignEnv# r# () fp p 1# ep s of { (# s1, w #) ->
254           (# s1, finalizeForeign w #) }}
255
256 finalizeForeign :: Weak# () -> IO ()
257 finalizeForeign w = IO $ \s ->
258   case finalizeWeak# w s of
259     (# s1, 0#, _ #) -> (# s1, () #)
260     (# s1, _ , f #) -> f s1
261
262 addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()
263 -- ^This function adds a finalizer to the given @ForeignPtr@.  The
264 -- finalizer will run /before/ all other finalizers for the same
265 -- object which have already been registered.
266 --
267 -- This is a variant of @addForeignPtrFinalizer@, where the finalizer
268 -- is an arbitrary @IO@ action.  When it is invoked, the finalizer
269 -- will run in a new thread.
270 --
271 -- NB. Be very careful with these finalizers.  One common trap is that
272 -- if a finalizer references another finalized value, it does not
273 -- prevent that value from being finalized.  In particular, 'Handle's
274 -- are finalized objects, so a finalizer should not refer to a 'Handle'
275 -- (including @stdout@, @stdin@ or @stderr@).
276 --
277 addForeignPtrConcFinalizer (ForeignPtr _ c) finalizer = 
278   addForeignPtrConcFinalizer_ c finalizer
279
280 addForeignPtrConcFinalizer_ :: ForeignPtrContents -> IO () -> IO ()
281 addForeignPtrConcFinalizer_ (PlainForeignPtr r) finalizer = do
282   noFinalizers <- noMixing HaskellFinalizers r (return finalizer)
283   if noFinalizers
284      then IO $ \s ->
285               case r of { IORef (STRef r#) ->
286               case mkWeak# r# () (foreignPtrFinalizer r) s of {  (# s1, _ #) ->
287               (# s1, () #) }}
288      else return ()
289 addForeignPtrConcFinalizer_ f@(MallocPtr fo r) finalizer = do
290   noFinalizers <- noMixing HaskellFinalizers r (return finalizer)
291   if noFinalizers
292      then  IO $ \s -> 
293                case mkWeak# fo () (do foreignPtrFinalizer r; touch f) s of
294                   (# s1, _ #) -> (# s1, () #)
295      else return ()
296
297 addForeignPtrConcFinalizer_ _ _ =
298   error "GHC.ForeignPtr: attempt to add a finalizer to plain pointer"
299
300 noMixing ::
301   Finalizers -> IORef (Finalizers, [IO ()]) -> IO (IO ()) -> IO Bool
302 noMixing ftype0 r mkF = do
303   (ftype, fs) <- readIORef r
304   if ftype /= NoFinalizers && ftype /= ftype0
305      then error ("GHC.ForeignPtr: attempt to mix Haskell and C finalizers " ++
306                  "in the same ForeignPtr")
307      else do
308        f <- mkF
309        writeIORef r (ftype0, f : fs)
310        return (null fs)
311
312 foreignPtrFinalizer :: IORef (Finalizers, [IO ()]) -> IO ()
313 foreignPtrFinalizer r = do (_, fs) <- readIORef r; sequence_ fs
314
315 newForeignPtr_ :: Ptr a -> IO (ForeignPtr a)
316 -- ^Turns a plain memory reference into a foreign pointer that may be
317 -- associated with finalizers by using 'addForeignPtrFinalizer'.
318 newForeignPtr_ (Ptr obj) =  do
319   r <- newIORef (NoFinalizers, [])
320   return (ForeignPtr obj (PlainForeignPtr r))
321
322 touchForeignPtr :: ForeignPtr a -> IO ()
323 -- ^This function ensures that the foreign object in
324 -- question is alive at the given place in the sequence of IO
325 -- actions. In particular 'Foreign.ForeignPtr.withForeignPtr'
326 -- does a 'touchForeignPtr' after it
327 -- executes the user action.
328 -- 
329 -- Note that this function should not be used to express dependencies
330 -- between finalizers on 'ForeignPtr's.  For example, if the finalizer
331 -- for a 'ForeignPtr' @F1@ calls 'touchForeignPtr' on a second
332 -- 'ForeignPtr' @F2@, then the only guarantee is that the finalizer
333 -- for @F2@ is never started before the finalizer for @F1@.  They
334 -- might be started together if for example both @F1@ and @F2@ are
335 -- otherwise unreachable, and in that case the scheduler might end up
336 -- running the finalizer for @F2@ first.
337 --
338 -- In general, it is not recommended to use finalizers on separate
339 -- objects with ordering constraints between them.  To express the
340 -- ordering robustly requires explicit synchronisation using @MVar@s
341 -- between the finalizers, but even then the runtime sometimes runs
342 -- multiple finalizers sequentially in a single thread (for
343 -- performance reasons), so synchronisation between finalizers could
344 -- result in artificial deadlock.  Another alternative is to use
345 -- explicit reference counting.
346 --
347 touchForeignPtr (ForeignPtr _ r) = touch r
348
349 touch :: ForeignPtrContents -> IO ()
350 touch r = IO $ \s -> case touch# r s of s' -> (# s', () #)
351
352 unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
353 -- ^This function extracts the pointer component of a foreign
354 -- pointer.  This is a potentially dangerous operations, as if the
355 -- argument to 'unsafeForeignPtrToPtr' is the last usage
356 -- occurrence of the given foreign pointer, then its finalizer(s) will
357 -- be run, which potentially invalidates the plain pointer just
358 -- obtained.  Hence, 'touchForeignPtr' must be used
359 -- wherever it has to be guaranteed that the pointer lives on - i.e.,
360 -- has another usage occurrence.
361 --
362 -- To avoid subtle coding errors, hand written marshalling code
363 -- should preferably use 'Foreign.ForeignPtr.withForeignPtr' rather
364 -- than combinations of 'unsafeForeignPtrToPtr' and
365 -- 'touchForeignPtr'.  However, the latter routines
366 -- are occasionally preferred in tool generated marshalling code.
367 unsafeForeignPtrToPtr (ForeignPtr fo _) = Ptr fo
368
369 castForeignPtr :: ForeignPtr a -> ForeignPtr b
370 -- ^This function casts a 'ForeignPtr'
371 -- parameterised by one type into another type.
372 castForeignPtr f = unsafeCoerce# f
373
374 -- | Causes the finalizers associated with a foreign pointer to be run
375 -- immediately.
376 finalizeForeignPtr :: ForeignPtr a -> IO ()
377 finalizeForeignPtr (ForeignPtr _ (PlainPtr _)) = return () -- no effect
378 finalizeForeignPtr (ForeignPtr _ foreignPtr) = do
379         (ftype, finalizers) <- readIORef refFinalizers
380         sequence_ finalizers
381         writeIORef refFinalizers (ftype, [])
382         where
383                 refFinalizers = case foreignPtr of
384                         (PlainForeignPtr ref) -> ref
385                         (MallocPtr     _ ref) -> ref
386                         PlainPtr _            ->
387                             error "finalizeForeignPtr PlainPtr"
388