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