[project @ 2003-01-23 11:46:57 by ross]
[ghc-base.git] / Foreign / ForeignPtr.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Foreign.ForeignPtr
5 -- Copyright   :  (c) The University of Glasgow 2001
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  ffi@haskell.org
9 -- Stability   :  provisional
10 -- Portability :  portable
11 --
12 -- The 'ForeignPtr' type and operations.  This module is part of the
13 -- Foreign Function Interface (FFI) and will usually be imported via
14 -- the "Foreign" module.
15 --
16 -----------------------------------------------------------------------------
17
18 module Foreign.ForeignPtr
19         ( 
20         -- * Finalised data pointers
21           ForeignPtr             -- abstract, instance of: Eq, Ord, Show
22         , newForeignPtr          -- :: Ptr a -> IO () -> IO (ForeignPtr a)
23         , addForeignPtrFinalizer -- :: ForeignPtr a -> IO () -> IO ()
24         , withForeignPtr         -- :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
25         , foreignPtrToPtr        -- :: ForeignPtr a -> Ptr a
26         , touchForeignPtr        -- :: ForeignPtr a -> IO ()
27         , castForeignPtr         -- :: ForeignPtr a -> ForeignPtr b
28
29 #ifndef __NHC__
30         , mallocForeignPtr      --  :: Storable a => IO (ForeignPtr a)
31         , mallocForeignPtrBytes --  :: Int -> IO (ForeignPtr a)
32         , mallocForeignPtrArray --  :: Storable a => Int -> IO (ForeignPtr a)
33         , mallocForeignPtrArray0 -- :: Storable a => Int -> IO (ForeignPtr a)
34 #endif
35         ) 
36         where
37
38 #ifndef __NHC__
39 import Foreign.Ptr
40 import Foreign.Storable
41 import Data.Dynamic
42 #endif
43
44 #ifdef __GLASGOW_HASKELL__
45 import GHC.Base
46 import GHC.IOBase
47 import GHC.Num
48 import GHC.Ptr  ( Ptr(..) )
49 import GHC.Err
50 import GHC.Show
51 #endif
52
53 #ifdef __NHC__
54 import NHC.FFI
55   ( ForeignPtr
56   , newForeignPtr
57   , addForeignPtrFinalizer
58   , withForeignPtr
59   , foreignPtrToPtr
60   , touchForeignPtr
61   , castForeignPtr
62   )
63 #endif
64
65 #ifdef __HUGS__
66 import Hugs.ForeignPtr
67 #endif
68
69 #ifndef __NHC__
70 #include "Dynamic.h"
71 INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr")
72 #endif
73
74 #ifdef __GLASGOW_HASKELL__
75 -- |The type 'ForeignPtr' represents references to objects that are
76 -- maintained in a foreign language, i.e., that are not part of the
77 -- data structures usually managed by the Haskell storage manager.
78 -- The essential difference between 'ForeignPtr's and vanilla memory
79 -- references of type @Ptr a@ is that the former may be associated
80 -- with /finalisers/. A finaliser is a routine that is invoked when
81 -- the Haskell storage manager detects that - within the Haskell heap
82 -- and stack - there are no more references left that are pointing to
83 -- the 'ForeignPtr'.  Typically, the finaliser will, then, invoke
84 -- routines in the foreign language that free the resources bound by
85 -- the foreign object.
86 --
87 -- The 'ForeignPtr' is parameterised in the same way as 'Ptr'.  The
88 -- type argument of 'ForeignPtr' should normally be an instance of
89 -- class 'Storable'.
90 --
91 data ForeignPtr a 
92   = ForeignPtr ForeignObj#
93   | MallocPtr  (MutableByteArray# RealWorld)
94
95 instance Eq (ForeignPtr a) where 
96     p == q  =  foreignPtrToPtr p == foreignPtrToPtr q
97
98 instance Ord (ForeignPtr a) where 
99     compare p q  =  compare (foreignPtrToPtr p) (foreignPtrToPtr q)
100
101 instance Show (ForeignPtr a) where
102     showsPrec p f = showsPrec p (foreignPtrToPtr f)
103
104
105 newForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
106 -- ^Turns a plain memory reference into a foreign object
107 -- by associating a finaliser - given by the monadic operation
108 -- - with the reference.  The finaliser will be executed after
109 -- the last reference to the foreign object is dropped.  Note
110 -- that there is no guarantee on how soon the finaliser is
111 -- executed after the last reference was dropped; this depends
112 -- on the details of the Haskell storage manager. The only
113 -- guarantee is that the finaliser runs before the program
114 -- terminates.
115 newForeignPtr p finalizer
116   = do fObj <- mkForeignPtr p
117        addForeignPtrFinalizer fObj finalizer
118        return fObj
119
120 -- | allocates some memory and returns a ForeignPtr to it.  The memory
121 -- will be released automatically when the ForeignPtr is discarded.
122 --
123 -- @mallocForeignPtr@ is equivalent to
124 --
125 -- >    do { p <- malloc; newForeignPtr p free }
126 -- 
127 -- although it may be implemented differently internally.  You may not
128 -- assume that the memory returned by 'mallocForeignPtr' has been
129 -- allocated with C's @malloc()@.
130
131 mallocForeignPtr :: Storable a => IO (ForeignPtr a)
132 mallocForeignPtr = doMalloc undefined
133   where doMalloc :: Storable a => a -> IO (ForeignPtr a)
134         doMalloc a = IO $ \s ->
135           case newPinnedByteArray# size s of { (# s, mbarr# #) ->
136            (# s, MallocPtr mbarr# #)
137           }
138           where (I# size) = sizeOf a
139
140 -- | similar to 'mallocForeignPtr', except that the size of the memory required
141 -- is given explicitly as a number of bytes.
142 mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
143 mallocForeignPtrBytes (I# size) = IO $ \s ->
144   case newPinnedByteArray# size s      of { (# s, mbarr# #) ->
145    (# s, MallocPtr mbarr# #)
146   }
147
148 addForeignPtrFinalizer :: ForeignPtr a -> IO () -> IO ()
149 -- ^This function adds another finaliser to the given
150 -- foreign object.  No guarantees are made on the order in
151 -- which multiple finalisers for a single object are run.
152 addForeignPtrFinalizer (ForeignPtr fo) finalizer = 
153   IO $ \s -> case mkWeak# fo () finalizer s of { (# s1, w #) -> (# s1, () #) }
154 addForeignPtrFinalizer (MallocPtr fo) finalizer = 
155   IO $ \s -> case mkWeak# fo () finalizer s of { (# s1, w #) -> (# s1, () #) }
156
157 mkForeignPtr :: Ptr a -> IO (ForeignPtr a) {- not exported -}
158 mkForeignPtr (Ptr obj) =  IO ( \ s# ->
159     case mkForeignObj# obj s# of
160       (# s1#, fo# #) -> (# s1#,  ForeignPtr fo# #) )
161
162 touchForeignPtr :: ForeignPtr a -> IO ()
163 -- ^This function ensures that the foreign object in
164 -- question is alive at the given place in the sequence of IO
165 -- actions. In particular 'withForeignPtr'
166 -- does a 'touchForeignPtr' after it
167 -- executes the user action.
168 -- 
169 -- This function can be used to express liveness
170 -- dependencies between 'ForeignPtr's: for
171 -- example, if the finalizer for one
172 -- 'ForeignPtr' touches a second
173 -- 'ForeignPtr', then it is ensured that the
174 -- second 'ForeignPtr' will stay alive at
175 -- least as long as the first.  This can be useful when you
176 -- want to manipulate /interior pointers/ to
177 -- a foreign structure: you can use
178 -- 'touchForeignObj' to express the
179 -- requirement that the exterior pointer must not be finalized
180 -- until the interior pointer is no longer referenced.
181 touchForeignPtr (ForeignPtr fo) 
182    = IO $ \s -> case touch# fo s of s -> (# s, () #)
183 touchForeignPtr (MallocPtr fo) 
184    = IO $ \s -> case touch# fo s of s -> (# s, () #)
185
186 withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
187 -- ^This is a way to look at the pointer living inside a
188 -- foreign object.  This function takes a function which is
189 -- applied to that pointer. The resulting 'IO' action is then
190 -- executed. The foreign object is kept alive at least during
191 -- the whole action, even if it is not used directly
192 -- inside. Note that it is not safe to return the pointer from
193 -- the action and use it after the action completes. All uses
194 -- of the pointer should be inside the
195 -- 'withForeignPtr' bracket.  The reason for
196 -- this unsafety is the same as for
197 -- 'foreignPtrToPtr' below: the finalizer
198 -- may run earlier than expected, because the compiler can only
199 -- track usage of the 'ForeignPtr' object, not
200 -- a 'Ptr' object made from it.
201 --
202 -- This function is normally used for marshalling data to
203 -- or from the object pointed to by the
204 -- 'ForeignPtr', using the operations from the
205 -- 'Storable' class.
206 withForeignPtr fo io
207   = do r <- io (foreignPtrToPtr fo)
208        touchForeignPtr fo
209        return r
210
211 foreignPtrToPtr :: ForeignPtr a -> Ptr a
212 -- ^This function extracts the pointer component of a foreign
213 -- pointer.  This is a potentially dangerous operations, as if the
214 -- argument to 'foreignPtrToPtr' is the last usage
215 -- occurence of the given foreign pointer, then its finaliser(s) will
216 -- be run, which potentially invalidates the plain pointer just
217 -- obtained.  Hence, 'touchForeignPtr' must be used
218 -- wherever it has to be guaranteed that the pointer lives on - i.e.,
219 -- has another usage occurrence.
220 --
221 -- To avoid subtle coding errors, hand written marshalling code
222 -- should preferably use 'withForeignPtr' rather
223 -- than combinations of 'foreignPtrToPtr' and
224 -- 'touchForeignPtr'.  However, the later routines
225 -- are occasionally preferred in tool generated marshalling code.
226 foreignPtrToPtr (ForeignPtr fo) = Ptr (foreignObjToAddr# fo)
227 foreignPtrToPtr (MallocPtr  fo) = Ptr (byteArrayContents# (unsafeCoerce# fo))
228
229 castForeignPtr :: ForeignPtr a -> ForeignPtr b
230 -- ^This function casts a 'ForeignPtr'
231 -- parameterised by one type into another type.
232 castForeignPtr (ForeignPtr a) = ForeignPtr a
233 castForeignPtr (MallocPtr  a) = MallocPtr  a
234 #endif
235
236 #ifndef __NHC__
237 mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a)
238 mallocForeignPtrArray  = doMalloc undefined
239   where
240     doMalloc            :: Storable a => a -> Int -> IO (ForeignPtr a)
241     doMalloc dummy size  = mallocForeignPtrBytes (size * sizeOf dummy)
242
243 mallocForeignPtrArray0      :: Storable a => Int -> IO (ForeignPtr a)
244 mallocForeignPtrArray0 size  = mallocForeignPtrArray (size + 1)
245 #endif