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