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