[project @ 2003-03-26 15:25:46 by simonmar]
[ghc-base.git] / GHC / ForeignPtr.hs
1 {-# OPTIONS -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         newForeignPtr,
20         mallocForeignPtr,
21         mallocForeignPtrBytes,
22         addForeignPtrFinalizer, 
23         touchForeignPtr,
24         withForeignPtr,
25         foreignPtrToPtr,
26         castForeignPtr,
27         newConcForeignPtr,
28         addForeignPtrConcFinalizer,
29   ) where
30
31 import Control.Monad    ( sequence_ )
32 import Foreign.Ptr
33 import Foreign.Storable
34 import Data.Dynamic
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 /finalisers/. A finaliser 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 finaliser 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  =  foreignPtrToPtr p == foreignPtrToPtr q
65
66 instance Ord (ForeignPtr a) where
67     compare p q  =  compare (foreignPtrToPtr p) (foreignPtrToPtr q)
68
69 instance Show (ForeignPtr a) where
70     showsPrec p f = showsPrec p (foreignPtrToPtr f)
71
72 #include "Dynamic.h"
73 INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr")
74
75 newForeignPtr :: Ptr a -> FunPtr (Ptr a -> IO ()) -> IO (ForeignPtr a)
76 -- ^Turns a plain memory reference into a foreign object by
77 -- associating a finaliser - a foreign function given by the @FunPtr@
78 -- - with the reference.  The finaliser will be executed after the
79 -- last reference to the foreign object is dropped.  Note that there
80 -- is no guarantee on how soon the finaliser is executed after the
81 -- last reference was dropped; this depends on the details of the
82 -- Haskell storage manager. The only guarantee is that the finaliser
83 -- runs before the program terminates.
84 newForeignPtr p finalizer
85   = do fObj <- mkForeignPtr p
86        addForeignPtrFinalizer fObj finalizer
87        return fObj
88
89 newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
90 -- ^Turns a plain memory reference into a foreign object
91 -- by associating a finaliser - given by the monadic operation
92 -- - with the reference.  The finaliser will be executed after
93 -- the last reference to the foreign object is dropped.  Note
94 -- that there is no guarantee on how soon the finaliser is
95 -- executed after the last reference was dropped; this depends
96 -- on the details of the Haskell storage manager. The only
97 -- guarantee is that the finaliser runs before the program
98 -- terminates.
99 --
100 -- The finalizer, when invoked, will run in a separate thread.
101 --
102 newConcForeignPtr p finalizer
103   = do fObj <- mkForeignPtr p
104        addForeignPtrConcFinalizer fObj finalizer
105        return fObj
106
107 mallocForeignPtr :: Storable a => IO (ForeignPtr a)
108 -- ^ allocates some memory and returns a ForeignPtr to it.  The memory
109 -- will be released automatically when the ForeignPtr is discarded.
110 --
111 -- @mallocForeignPtr@ is equivalent to
112 --
113 -- >    do { p <- malloc; newForeignPtr p free }
114 -- 
115 -- although it may be implemented differently internally.  You may not
116 -- assume that the memory returned by 'mallocForeignPtr' has been
117 -- allocated with C's @malloc()@.
118 mallocForeignPtr = doMalloc undefined
119   where doMalloc :: Storable a => a -> IO (ForeignPtr a)
120         doMalloc a = do
121           r <- newIORef []
122           IO $ \s ->
123             case newPinnedByteArray# size s of { (# s, mbarr# #) ->
124              (# s, MallocPtr mbarr# r #)
125             }
126             where (I# size) = sizeOf a
127
128 -- | similar to 'mallocForeignPtr', except that the size of the memory required
129 -- is given explicitly as a number of bytes.
130 mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
131 mallocForeignPtrBytes (I# size) = do 
132   r <- newIORef []
133   IO $ \s ->
134      case newPinnedByteArray# size s      of { (# s, mbarr# #) ->
135        (# s, MallocPtr mbarr# r #)
136      }
137
138 addForeignPtrFinalizer :: ForeignPtr a -> FunPtr (Ptr a -> IO ()) -> IO ()
139 -- ^This function adds a finaliser to the given foreign object.  The
140 -- finalizer will run /before/ all other finalizers for the same
141 -- object which have already been registered.
142 addForeignPtrFinalizer fptr finalizer = 
143   addForeignPtrConcFinalizer fptr 
144         (mkFinalizer finalizer (foreignPtrToPtr fptr))
145
146 addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()
147 -- ^This function adds a finaliser to the given @ForeignPtr@.  The
148 -- finalizer will run /before/ all other finalizers for the same
149 -- object which have already been registered.
150 --
151 -- This is a variant of @addForeignPtrFinalizer@, where the finalizer
152 -- is an arbitrary @IO@ action.  When it is invoked, the finalizer
153 -- will run in a new thread.
154 --
155 addForeignPtrConcFinalizer f@(ForeignPtr fo r) finalizer = do
156   fs <- readIORef r
157   writeIORef r (finalizer : fs)
158   if (null fs)
159      then IO $ \s ->
160               let p = foreignPtrToPtr f in
161               case mkWeak# fo () (foreignPtrFinalizer r p) s of 
162                  (# s1, w #) -> (# s1, () #)
163      else return ()
164 addForeignPtrConcFinalizer f@(MallocPtr fo r) finalizer = do 
165   fs <- readIORef r
166   writeIORef r (finalizer : fs)
167   if (null fs)
168      then  IO $ \s -> 
169                let p = foreignPtrToPtr f in
170                case mkWeak# fo () (foreignPtrFinalizer r p) s of 
171                   (# s1, w #) -> (# s1, () #)
172      else return ()
173
174 foreign import ccall "dynamic" 
175   mkFinalizer :: FunPtr (Ptr a -> IO ()) -> Ptr a -> IO ()
176
177 foreignPtrFinalizer :: IORef [IO ()] -> Ptr a -> IO ()
178 foreignPtrFinalizer r p = do
179   fs <- readIORef r
180   sequence_ fs
181
182 mkForeignPtr :: Ptr a -> IO (ForeignPtr a) {- not exported -}
183 mkForeignPtr (Ptr obj) =  do
184   r <- newIORef []
185   IO $ \ s# ->
186     case mkForeignObj# obj s# of
187       (# s1#, fo# #) -> (# s1#,  ForeignPtr fo# r #)
188
189 touchForeignPtr :: ForeignPtr a -> IO ()
190 -- ^This function ensures that the foreign object in
191 -- question is alive at the given place in the sequence of IO
192 -- actions. In particular 'withForeignPtr'
193 -- does a 'touchForeignPtr' after it
194 -- executes the user action.
195 -- 
196 -- This function can be used to express liveness
197 -- dependencies between 'ForeignPtr's: for
198 -- example, if the finalizer for one
199 -- 'ForeignPtr' touches a second
200 -- 'ForeignPtr', then it is ensured that the
201 -- second 'ForeignPtr' will stay alive at
202 -- least as long as the first.  This can be useful when you
203 -- want to manipulate /interior pointers/ to
204 -- a foreign structure: you can use
205 -- 'touchForeignObj' to express the
206 -- requirement that the exterior pointer must not be finalized
207 -- until the interior pointer is no longer referenced.
208 touchForeignPtr (ForeignPtr fo r)
209    = IO $ \s -> case touch# fo s of s -> (# s, () #)
210 touchForeignPtr (MallocPtr fo r)
211    = IO $ \s -> case touch# fo s of s -> (# s, () #)
212
213 withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
214 -- ^This is a way to look at the pointer living inside a
215 -- foreign object.  This function takes a function which is
216 -- applied to that pointer. The resulting 'IO' action is then
217 -- executed. The foreign object is kept alive at least during
218 -- the whole action, even if it is not used directly
219 -- inside. Note that it is not safe to return the pointer from
220 -- the action and use it after the action completes. All uses
221 -- of the pointer should be inside the
222 -- 'withForeignPtr' bracket.  The reason for
223 -- this unsafety is the same as for
224 -- 'foreignPtrToPtr' below: the finalizer
225 -- may run earlier than expected, because the compiler can only
226 -- track usage of the 'ForeignPtr' object, not
227 -- a 'Ptr' object made from it.
228 --
229 -- This function is normally used for marshalling data to
230 -- or from the object pointed to by the
231 -- 'ForeignPtr', using the operations from the
232 -- 'Storable' class.
233 withForeignPtr fo io
234   = do r <- io (foreignPtrToPtr fo)
235        touchForeignPtr fo
236        return r
237
238 foreignPtrToPtr :: ForeignPtr a -> Ptr a
239 -- ^This function extracts the pointer component of a foreign
240 -- pointer.  This is a potentially dangerous operations, as if the
241 -- argument to 'foreignPtrToPtr' is the last usage
242 -- occurence of the given foreign pointer, then its finaliser(s) will
243 -- be run, which potentially invalidates the plain pointer just
244 -- obtained.  Hence, 'touchForeignPtr' must be used
245 -- wherever it has to be guaranteed that the pointer lives on - i.e.,
246 -- has another usage occurrence.
247 --
248 -- To avoid subtle coding errors, hand written marshalling code
249 -- should preferably use 'withForeignPtr' rather
250 -- than combinations of 'foreignPtrToPtr' and
251 -- 'touchForeignPtr'.  However, the later routines
252 -- are occasionally preferred in tool generated marshalling code.
253 foreignPtrToPtr (ForeignPtr fo r) = Ptr (foreignObjToAddr# fo)
254 foreignPtrToPtr (MallocPtr  fo r) = Ptr (byteArrayContents# (unsafeCoerce# fo))
255
256 castForeignPtr :: ForeignPtr a -> ForeignPtr b
257 -- ^This function casts a 'ForeignPtr'
258 -- parameterised by one type into another type.
259 castForeignPtr f = unsafeCoerce# f