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