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