[project @ 2002-10-11 11:05:20 by malcolm]
[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
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 #ifdef __GLASGOW_HASKELL__
30         -- * GHC extensions
31         , mallocForeignPtr      --  :: Storable a => IO (ForeignPtr a)
32         , mallocForeignPtrBytes --  :: Int -> IO (ForeignPtr a)
33 #endif
34         ) 
35         where
36
37 #ifdef __GLASGOW_HASKELL__
38 import Foreign.Ptr
39 import Foreign.Storable
40 import Data.Dynamic
41
42 import GHC.Base
43 import GHC.IOBase
44 import GHC.Num
45 import GHC.Ptr  ( Ptr(..) )
46 import GHC.Err
47 #endif
48
49 #ifdef __NHC__
50 import NHC.FFI
51   ( ForeignPtr
52   , newForeignPtr
53   , addForeignPtrFinalizer
54   , withForeignPtr
55   , foreignPtrToPtr
56   , touchForeignPtr
57   , castForeignPtr
58   )
59 #endif
60
61 #ifdef __GLASGOW_HASKELL__
62 #include "Dynamic.h"
63 INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr")
64
65 -- |The type 'ForeignPtr' represents references to objects that are
66 -- maintained in a foreign language, i.e., that are not part of the
67 -- data structures usually managed by the Haskell storage manager.
68 -- The essential difference between 'ForeignPtr's and vanilla memory
69 -- references of type @Ptr a@ is that the former may be associated
70 -- with /finalisers/. A finaliser is a routine that is invoked when
71 -- the Haskell storage manager detects that - within the Haskell heap
72 -- and stack - there are no more references left that are pointing to
73 -- the 'ForeignPtr'.  Typically, the finaliser will, then, invoke
74 -- routines in the foreign language that free the resources bound by
75 -- the foreign object.
76 --
77 -- The 'ForeignPtr' is parameterised in the same way as 'Ptr'.  The
78 -- type argument of 'ForeignPtr' should normally be an instance of
79 -- class 'Storable'.
80 --
81 data ForeignPtr a 
82   = ForeignPtr ForeignObj#
83   | MallocPtr  (MutableByteArray# RealWorld)
84
85 eqForeignPtr  :: ForeignPtr a -> ForeignPtr a -> Bool
86 eqForeignPtr (ForeignPtr fo1#) (ForeignPtr fo2#) = eqForeignObj# fo1# fo2#
87 eqForeignPtr (MallocPtr fo1#)  (MallocPtr fo2#)  = sameMutableByteArray# fo1# fo2#
88 eqForeignPtr _ _ = False
89
90 instance Eq (ForeignPtr a) where 
91     p == q = eqForeignPtr p q
92
93 newForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
94 -- ^Turns a plain memory reference into a foreign object
95 -- by associating a finaliser - given by the monadic operation
96 -- - with the reference.  The finaliser will be executed after
97 -- the last reference to the foreign object is dropped.  Note
98 -- that there is no guarantee on how soon the finaliser is
99 -- executed after the last reference was dropped; this depends
100 -- on the details of the Haskell storage manager. The only
101 -- guarantee is that the finaliser runs before the program
102 -- terminates.
103 newForeignPtr p finalizer
104   = do fObj <- mkForeignPtr p
105        addForeignPtrFinalizer fObj finalizer
106        return fObj
107
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
119 mallocForeignPtr :: Storable a => IO (ForeignPtr a)
120 mallocForeignPtr = doMalloc undefined
121   where doMalloc :: Storable a => a -> IO (ForeignPtr a)
122         doMalloc a = IO $ \s ->
123           case newPinnedByteArray# size s of { (# s, mbarr# #) ->
124            (# s, MallocPtr mbarr# #)
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) = IO $ \s ->
132   case newPinnedByteArray# size s      of { (# s, mbarr# #) ->
133    (# s, MallocPtr mbarr# #)
134   }
135
136 addForeignPtrFinalizer :: ForeignPtr a -> IO () -> IO ()
137 -- ^This function adds another finaliser to the given
138 -- foreign object.  No guarantees are made on the order in
139 -- which multiple finalisers for a single object are run.
140 addForeignPtrFinalizer (ForeignPtr fo) finalizer = 
141   IO $ \s -> case mkWeak# fo () finalizer s of { (# s1, w #) -> (# s1, () #) }
142 addForeignPtrFinalizer (MallocPtr fo) finalizer = 
143   IO $ \s -> case mkWeak# fo () finalizer s of { (# s1, w #) -> (# s1, () #) }
144
145 mkForeignPtr :: Ptr a -> IO (ForeignPtr a) {- not exported -}
146 mkForeignPtr (Ptr obj) =  IO ( \ s# ->
147     case mkForeignObj# obj s# of
148       (# s1#, fo# #) -> (# s1#,  ForeignPtr fo# #) )
149
150 touchForeignPtr :: ForeignPtr a -> IO ()
151 -- ^This function ensures that the foreign object in
152 -- question is alive at the given place in the sequence of IO
153 -- actions. In particular 'withForeignPtr'
154 -- does a 'touchForeignPtr' after it
155 -- executes the user action.
156 -- 
157 -- This function can be used to express liveness
158 -- dependencies between 'ForeignPtr's: for
159 -- example, if the finalizer for one
160 -- 'ForeignPtr' touches a second
161 -- 'ForeignPtr', then it is ensured that the
162 -- second 'ForeignPtr' will stay alive at
163 -- least as long as the first.  This can be useful when you
164 -- want to manipulate /interior pointers/ to
165 -- a foreign structure: you can use
166 -- 'touchForeignObj' to express the
167 -- requirement that the exterior pointer must not be finalized
168 -- until the interior pointer is no longer referenced.
169 touchForeignPtr (ForeignPtr fo) 
170    = IO $ \s -> case touch# fo s of s -> (# s, () #)
171 touchForeignPtr (MallocPtr fo) 
172    = IO $ \s -> case touch# fo s of s -> (# s, () #)
173
174 withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
175 -- ^This is a way to look at the pointer living inside a
176 -- foreign object.  This function takes a function which is
177 -- applied to that pointer. The resulting 'IO' action is then
178 -- executed. The foreign object is kept alive at least during
179 -- the whole action, even if it is not used directly
180 -- inside. Note that it is not safe to return the pointer from
181 -- the action and use it after the action completes. All uses
182 -- of the pointer should be inside the
183 -- 'withForeignPtr' bracket.  The reason for
184 -- this unsafety is the same as for
185 -- 'foreignPtrToPtr' below: the finalizer
186 -- may run earlier than expected, because the compiler can only
187 -- track usage of the 'ForeignPtr' object, not
188 -- a 'Ptr' object made from it.
189 --
190 -- This function is normally used for marshalling data to
191 -- or from the object pointed to by the
192 -- 'ForeignPtr', using the operations from the
193 -- 'Storable' class.
194 withForeignPtr fo io
195   = do r <- io (foreignPtrToPtr fo)
196        touchForeignPtr fo
197        return r
198
199 foreignPtrToPtr :: ForeignPtr a -> Ptr a
200 -- ^This function extracts the pointer component of a foreign
201 -- pointer.  This is a potentially dangerous operations, as if the
202 -- argument to 'foreignPtrToPtr' is the last usage
203 -- occurence of the given foreign pointer, then its finaliser(s) will
204 -- be run, which potentially invalidates the plain pointer just
205 -- obtained.  Hence, 'touchForeignPtr' must be used
206 -- wherever it has to be guaranteed that the pointer lives on - i.e.,
207 -- has another usage occurrence.
208 --
209 -- To avoid subtle coding errors, hand written marshalling code
210 -- should preferably use 'withForeignPtr' rather
211 -- than combinations of 'foreignPtrToPtr' and
212 -- 'touchForeignPtr'.  However, the later routines
213 -- are occasionally preferred in tool generated marshalling code.
214 foreignPtrToPtr (ForeignPtr fo) = Ptr (foreignObjToAddr# fo)
215 foreignPtrToPtr (MallocPtr  fo) = Ptr (byteArrayContents# (unsafeCoerce# fo))
216
217 castForeignPtr :: ForeignPtr a -> ForeignPtr b
218 -- ^This function casts a 'ForeignPtr'
219 -- parameterised by one type into another type.
220 castForeignPtr (ForeignPtr a) = ForeignPtr a
221 castForeignPtr (MallocPtr  a) = MallocPtr  a
222 #endif
223