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