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