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