9a83c25bcc47bddd8e2e2044b2423b19cb3ca691
[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         mallocForeignPtrBytes,
24         addForeignPtrFinalizer, 
25         touchForeignPtr,
26         unsafeForeignPtrToPtr,
27         castForeignPtr,
28         newConcForeignPtr,
29         addForeignPtrConcFinalizer,
30         finalizeForeignPtr
31   ) where
32
33 import Control.Monad    ( sequence_ )
34 import Foreign.Ptr
35 import Foreign.Storable
36
37 import GHC.Base
38 import GHC.IOBase
39 import GHC.STRef        ( STRef(..) )
40 import GHC.Ptr          ( Ptr(..) )
41 import GHC.Err
42 import GHC.Show
43
44 -- |The type 'ForeignPtr' represents references to objects that are
45 -- maintained in a foreign language, i.e., that are not part of the
46 -- data structures usually managed by the Haskell storage manager.
47 -- The essential difference between 'ForeignPtr's and vanilla memory
48 -- references of type @Ptr a@ is that the former may be associated
49 -- with /finalizers/. A finalizer is a routine that is invoked when
50 -- the Haskell storage manager detects that - within the Haskell heap
51 -- and stack - there are no more references left that are pointing to
52 -- the 'ForeignPtr'.  Typically, the finalizer will, then, invoke
53 -- routines in the foreign language that free the resources bound by
54 -- the foreign object.
55 --
56 -- The 'ForeignPtr' is parameterised in the same way as 'Ptr'.  The
57 -- type argument of 'ForeignPtr' should normally be an instance of
58 -- class 'Storable'.
59 --
60 data ForeignPtr a = ForeignPtr Addr# ForeignPtrContents
61         -- we cache the Addr# in the ForeignPtr object, but attach
62         -- the finalizer to the IORef (or the MutableByteArray# in
63         -- the case of a MallocPtr).  The aim of the representation
64         -- is to make withForeignPtr efficient; in fact, withForeignPtr
65         -- should be just as efficient as unpacking a Ptr, and multiple
66         -- withForeignPtrs can share an unpacked ForeignPtr.  Note
67         -- that touchForeignPtr only has to touch the ForeignPtrContents
68         -- object, because that ensures that whatever the finalizer is
69         -- attached to is kept alive.
70
71 data ForeignPtrContents 
72   = PlainNoFinalizer
73   | PlainWithFinalizer     !(IORef [IO ()])
74   | MallocPtrNoFinalizer   (MutableByteArray# RealWorld)
75   | MallocPtrWithFinalizer (MutableByteArray# RealWorld) !(IORef [IO ()])
76   -- we optimise the no-finalizer case, which is especially common
77   -- with a MallocPtr.  mallocForeignPtr doesn't have to create an
78   -- IORef, or set up a weak pointer.
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 -- |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 newConcForeignPtr p finalizer
106   = do fObj <- newForeignPtr_ p
107        addForeignPtrConcFinalizer fObj finalizer
108        return fObj
109
110 mallocForeignPtr :: Storable a => IO (ForeignPtr a)
111 -- ^ Allocate some memory and return a 'ForeignPtr' to it.  The memory
112 -- will be released automatically when the 'ForeignPtr' is discarded.
113 --
114 -- 'mallocForeignPtr' is equivalent to
115 --
116 -- >    do { p <- malloc; newForeignPtr finalizerFree p }
117 -- 
118 -- although it may be implemented differently internally: you may not
119 -- assume that the memory returned by 'mallocForeignPtr' has been
120 -- allocated with 'Foreign.Marshal.Alloc.malloc'.
121 mallocForeignPtr = doMalloc undefined
122   where doMalloc :: Storable b => b -> IO (ForeignPtr b)
123         doMalloc a = do
124           IO $ \s ->
125             case newPinnedByteArray# size s of { (# s, mbarr# #) ->
126              (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
127                               (MallocPtrNoFinalizer mbarr#) #)
128             }
129             where (I# size) = sizeOf a
130
131 -- | This function is similar to 'mallocForeignPtr', except that the
132 -- size of the memory required is given explicitly as a number of bytes.
133 mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
134 mallocForeignPtrBytes (I# size) = do 
135   IO $ \s ->
136      case newPinnedByteArray# size s      of { (# s, mbarr# #) ->
137        (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
138                         (MallocPtrNoFinalizer mbarr#) #)
139      }
140
141 addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()
142 -- ^This function adds a finalizer to the given foreign object.  The
143 -- finalizer will run /before/ all other finalizers for the same
144 -- object which have already been registered.
145 addForeignPtrFinalizer finalizer fptr = 
146   addForeignPtrConcFinalizer fptr 
147         (mkFinalizer finalizer (unsafeForeignPtrToPtr fptr))
148
149 addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()
150 -- ^This function adds a finalizer to the given @ForeignPtr@.  The
151 -- finalizer will run /before/ all other finalizers for the same
152 -- object which have already been registered.
153 --
154 -- This is a variant of @addForeignPtrFinalizer@, where the finalizer
155 -- is an arbitrary @IO@ action.  When it is invoked, the finalizer
156 -- will run in a new thread.
157 --
158 -- NB. Be very careful with these finalizers.  One common trap is that
159 -- if a finalizer references another finalized value, it does not
160 -- prevent that value from being finalized.  In particular, 'Handle's
161 -- are finalized objects, so a finalizer should not refer to a 'Handle'
162 -- (including @stdout@, @stdin@ or @stderr@).
163 --
164 addForeignPtrConcFinalizer (ForeignPtr a c) finalizer = 
165   addForeignPtrConcFinalizer_ c finalizer
166
167 addForeignPtrConcFinalizer_ PlainNoFinalizer finalizer = do
168   r <- newIORef []
169   IO $ \s ->  case r of { IORef (STRef r#) ->
170               case mkWeak# r# () (foreignPtrFinalizer r) s of {  (# s1, w #) ->
171               (# s1, () #) }}
172   addForeignPtrConcFinalizer_ (PlainWithFinalizer r) finalizer
173
174 addForeignPtrConcFinalizer_ f@(PlainWithFinalizer r) finalizer = do
175   fs <- readIORef r
176   writeIORef r (finalizer : fs)
177
178 addForeignPtrConcFinalizer_ f@(MallocPtrNoFinalizer fo) finalizer = do
179   r <- newIORef []
180   IO $ \s -> case mkWeak# fo () (do foreignPtrFinalizer r; touch f) s of
181                   (# s1, w #) -> (# s1, () #)
182   addForeignPtrConcFinalizer_ (MallocPtrWithFinalizer fo r) finalizer
183
184 addForeignPtrConcFinalizer_ f@(MallocPtrWithFinalizer fo r) finalizer = do 
185   fs <- readIORef r
186   writeIORef r (finalizer : fs)
187
188 foreign import ccall "dynamic" 
189   mkFinalizer :: FinalizerPtr a -> Ptr a -> IO ()
190
191 foreignPtrFinalizer :: IORef [IO ()] -> IO ()
192 foreignPtrFinalizer r = do fs <- readIORef r; sequence_ fs
193
194 newForeignPtr_ :: Ptr a -> IO (ForeignPtr a)
195 -- ^Turns a plain memory reference into a foreign pointer that may be
196 -- associated with finalizers by using 'addForeignPtrFinalizer'.
197 newForeignPtr_ (Ptr obj) = return (ForeignPtr obj PlainNoFinalizer)
198
199 touchForeignPtr :: ForeignPtr a -> IO ()
200 -- ^This function ensures that the foreign object in
201 -- question is alive at the given place in the sequence of IO
202 -- actions. In particular 'Foreign.ForeignPtr.withForeignPtr'
203 -- does a 'touchForeignPtr' after it
204 -- executes the user action.
205 -- 
206 -- Note that this function should not be used to express liveness
207 -- dependencies between 'ForeignPtr's.  For example, if the finalizer
208 -- for a 'ForeignPtr' @F1@ calls 'touchForeignPtr' on a second
209 -- 'ForeignPtr' @F2@, then the only guarantee is that the finalizer
210 -- for @F2@ is never started before the finalizer for @F1@.  They
211 -- might be started together if for example both @F1@ and @F2@ are
212 -- otherwise unreachable, and in that case the scheduler might end up
213 -- running the finalizer for @F2@ first.
214 --
215 -- In general, it is not recommended to use finalizers on separate
216 -- objects with ordering constraints between them.  To express the
217 -- ordering robustly requires explicit synchronisation using @MVar@s
218 -- between the finalizers, but even then the runtime sometimes runs
219 -- multiple finalizers sequentially in a single thread (for
220 -- performance reasons), so synchronisation between finalizers could
221 -- result in artificial deadlock.
222 --
223 touchForeignPtr (ForeignPtr fo r) = touch r
224
225 touch r = IO $ \s -> case touch# r s of s -> (# s, () #)
226
227 unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
228 -- ^This function extracts the pointer component of a foreign
229 -- pointer.  This is a potentially dangerous operations, as if the
230 -- argument to 'unsafeForeignPtrToPtr' is the last usage
231 -- occurrence of the given foreign pointer, then its finalizer(s) will
232 -- be run, which potentially invalidates the plain pointer just
233 -- obtained.  Hence, 'touchForeignPtr' must be used
234 -- wherever it has to be guaranteed that the pointer lives on - i.e.,
235 -- has another usage occurrence.
236 --
237 -- To avoid subtle coding errors, hand written marshalling code
238 -- should preferably use 'Foreign.ForeignPtr.withForeignPtr' rather
239 -- than combinations of 'unsafeForeignPtrToPtr' and
240 -- 'touchForeignPtr'.  However, the later routines
241 -- are occasionally preferred in tool generated marshalling code.
242 unsafeForeignPtrToPtr (ForeignPtr fo r) = Ptr fo
243
244 castForeignPtr :: ForeignPtr a -> ForeignPtr b
245 -- ^This function casts a 'ForeignPtr'
246 -- parameterised by one type into another type.
247 castForeignPtr f = unsafeCoerce# f
248
249 -- | Causes the finalizers associated with a foreign pointer to be run
250 -- immediately.
251 finalizeForeignPtr :: ForeignPtr a -> IO ()
252 finalizeForeignPtr (ForeignPtr _ contents) = do
253   case contents of
254     PlainNoFinalizer           -> return ()
255     PlainWithFinalizer r       -> runFinalizers r
256     MallocPtrNoFinalizer _     -> return ()
257     MallocPtrWithFinalizer _ r -> runFinalizers r
258  where
259    runFinalizers r = do 
260      fs <- readIORef r
261      sequence_ fs
262      writeIORef r []