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