add WordPtr and IntPtr types to Foreign.Ptr, with associated conversions
[ghc-base.git] / GHC / ForeignPtr.hs
1 {-# OPTIONS_GHC -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 -- #hide
17 module GHC.ForeignPtr
18   (
19         ForeignPtr(..),
20         FinalizerPtr,
21         newForeignPtr_,
22         mallocForeignPtr,
23         mallocForeignPtrBytes,
24         addForeignPtrFinalizer, 
25         touchForeignPtr,
26         unsafeForeignPtrToPtr,
27         castForeignPtr,
28         newConcForeignPtr,
29         addForeignPtrConcFinalizer,
30         finalizeForeignPtr
31   ) where
32
33 import Control.Monad    ( sequence_ )
34 import Foreign.Storable
35 import Numeric          ( showHex )
36
37 import GHC.Show
38 import GHC.Num
39 import GHC.List         ( null, replicate, length )
40 import GHC.Base
41 import GHC.IOBase
42 import GHC.STRef        ( STRef(..) )
43 import GHC.Ptr          ( Ptr(..), FunPtr, castFunPtrToPtr )
44 import GHC.Err
45
46 -- |The type 'ForeignPtr' represents references to objects that are
47 -- maintained in a foreign language, i.e., that are not part of the
48 -- data structures usually managed by the Haskell storage manager.
49 -- The essential difference between 'ForeignPtr's and vanilla memory
50 -- references of type @Ptr a@ is that the former may be associated
51 -- with /finalizers/. A finalizer is a routine that is invoked when
52 -- the Haskell storage manager detects that - within the Haskell heap
53 -- and stack - there are no more references left that are pointing to
54 -- the 'ForeignPtr'.  Typically, the finalizer will, then, invoke
55 -- routines in the foreign language that free the resources bound by
56 -- the foreign object.
57 --
58 -- The 'ForeignPtr' is parameterised in the same way as 'Ptr'.  The
59 -- type argument of 'ForeignPtr' should normally be an instance of
60 -- class 'Storable'.
61 --
62 data ForeignPtr a = ForeignPtr Addr# ForeignPtrContents
63         -- we cache the Addr# in the ForeignPtr object, but attach
64         -- the finalizer to the IORef (or the MutableByteArray# in
65         -- the case of a MallocPtr).  The aim of the representation
66         -- is to make withForeignPtr efficient; in fact, withForeignPtr
67         -- should be just as efficient as unpacking a Ptr, and multiple
68         -- withForeignPtrs can share an unpacked ForeignPtr.  Note
69         -- that touchForeignPtr only has to touch the ForeignPtrContents
70         -- object, because that ensures that whatever the finalizer is
71         -- attached to is kept alive.
72
73 data ForeignPtrContents 
74   = PlainForeignPtr !(IORef [IO ()])
75   | MallocPtr (MutableByteArray# RealWorld) !(IORef [IO ()])
76
77 instance Eq (ForeignPtr a) where
78     p == q  =  unsafeForeignPtrToPtr p == unsafeForeignPtrToPtr q
79
80 instance Ord (ForeignPtr a) where
81     compare p q  =  compare (unsafeForeignPtrToPtr p) (unsafeForeignPtrToPtr q)
82
83 instance Show (ForeignPtr a) where
84     showsPrec p f = showsPrec p (unsafeForeignPtrToPtr f)
85
86 #include "MachDeps.h"
87
88 #if (WORD_SIZE_IN_BITS == 32 || WORD_SIZE_IN_BITS == 64)
89 instance Show (Ptr a) where
90    showsPrec p (Ptr a) rs = pad_out (showHex (word2Integer(int2Word#(addr2Int# a))) "") rs
91      where
92         -- want 0s prefixed to pad it out to a fixed length.
93        pad_out ls rs = 
94           '0':'x':(replicate (2*SIZEOF_HSPTR - length ls) '0') ++ ls ++ rs
95        -- word2Integer :: Word# -> Integer (stolen from Word.lhs)
96        word2Integer w = case word2Integer# w of
97                         (# s, d #) -> J# s d
98
99 instance Show (FunPtr a) where
100    showsPrec p = showsPrec p . castFunPtrToPtr
101 #endif
102
103 -- |A Finalizer is represented as a pointer to a foreign function that, at
104 -- finalisation time, gets as an argument a plain pointer variant of the
105 -- foreign pointer that the finalizer is associated with.
106 -- 
107 type FinalizerPtr a = FunPtr (Ptr a -> IO ())
108
109 newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
110 --
111 -- ^Turns a plain memory reference into a foreign object by
112 -- associating a finalizer - given by the monadic operation - with the
113 -- reference.  The storage manager will start the finalizer, in a
114 -- separate thread, some time after the last reference to the
115 -- @ForeignPtr@ is dropped.  There is no guarantee of promptness, and
116 -- in fact there is no guarantee that the finalizer will eventually
117 -- run at all.
118 --
119 -- Note that references from a finalizer do not necessarily prevent
120 -- another object from being finalized.  If A's finalizer refers to B
121 -- (perhaps using 'touchForeignPtr', then the only guarantee is that
122 -- B's finalizer will never be started before A's.  If both A and B
123 -- are unreachable, then both finalizers will start together.  See
124 -- 'touchForeignPtr' for more on finalizer ordering.
125 --
126 newConcForeignPtr p finalizer
127   = do fObj <- newForeignPtr_ p
128        addForeignPtrConcFinalizer fObj finalizer
129        return fObj
130
131 mallocForeignPtr :: Storable a => IO (ForeignPtr a)
132 -- ^ Allocate some memory and return a 'ForeignPtr' to it.  The memory
133 -- will be released automatically when the 'ForeignPtr' is discarded.
134 --
135 -- 'mallocForeignPtr' is equivalent to
136 --
137 -- >    do { p <- malloc; newForeignPtr finalizerFree p }
138 -- 
139 -- although it may be implemented differently internally: you may not
140 -- assume that the memory returned by 'mallocForeignPtr' has been
141 -- allocated with 'Foreign.Marshal.Alloc.malloc'.
142 --
143 -- GHC notes: 'mallocForeignPtr' has a heavily optimised
144 -- implementation in GHC.  It uses pinned memory in the garbage
145 -- collected heap, so the 'ForeignPtr' does not require a finalizer to
146 -- free the memory.  Use of 'mallocForeignPtr' and associated
147 -- functions is strongly recommended in preference to 'newForeignPtr'
148 -- with a finalizer.
149 -- 
150 mallocForeignPtr = doMalloc undefined
151   where doMalloc :: Storable b => b -> IO (ForeignPtr b)
152         doMalloc a = do
153           r <- newIORef []
154           IO $ \s ->
155             case newPinnedByteArray# size s of { (# s, mbarr# #) ->
156              (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
157                               (MallocPtr mbarr# r) #)
158             }
159             where (I# size) = sizeOf a
160
161 -- | This function is similar to 'mallocForeignPtr', except that the
162 -- size of the memory required is given explicitly as a number of bytes.
163 mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
164 mallocForeignPtrBytes (I# size) = do 
165   r <- newIORef []
166   IO $ \s ->
167      case newPinnedByteArray# size s      of { (# s, mbarr# #) ->
168        (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
169                         (MallocPtr mbarr# r) #)
170      }
171
172 addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()
173 -- ^This function adds a finalizer to the given foreign object.  The
174 -- finalizer will run /before/ all other finalizers for the same
175 -- object which have already been registered.
176 addForeignPtrFinalizer finalizer fptr = 
177   addForeignPtrConcFinalizer fptr 
178         (mkFinalizer finalizer (unsafeForeignPtrToPtr fptr))
179
180 addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()
181 -- ^This function adds a finalizer to the given @ForeignPtr@.  The
182 -- finalizer will run /before/ all other finalizers for the same
183 -- object which have already been registered.
184 --
185 -- This is a variant of @addForeignPtrFinalizer@, where the finalizer
186 -- is an arbitrary @IO@ action.  When it is invoked, the finalizer
187 -- will run in a new thread.
188 --
189 -- NB. Be very careful with these finalizers.  One common trap is that
190 -- if a finalizer references another finalized value, it does not
191 -- prevent that value from being finalized.  In particular, 'Handle's
192 -- are finalized objects, so a finalizer should not refer to a 'Handle'
193 -- (including @stdout@, @stdin@ or @stderr@).
194 --
195 addForeignPtrConcFinalizer (ForeignPtr a c) finalizer = 
196   addForeignPtrConcFinalizer_ c finalizer
197
198 addForeignPtrConcFinalizer_ f@(PlainForeignPtr r) finalizer = do
199   fs <- readIORef r
200   writeIORef r (finalizer : fs)
201   if (null fs)
202      then IO $ \s ->
203               case r of { IORef (STRef r#) ->
204               case mkWeak# r# () (foreignPtrFinalizer r) s of {  (# s1, w #) ->
205               (# s1, () #) }}
206      else return ()
207 addForeignPtrConcFinalizer_ f@(MallocPtr fo r) finalizer = do 
208   fs <- readIORef r
209   writeIORef r (finalizer : fs)
210   if (null fs)
211      then  IO $ \s -> 
212                case mkWeak# fo () (do foreignPtrFinalizer r; touch f) s of
213                   (# s1, w #) -> (# s1, () #)
214      else return ()
215
216 foreign import ccall "dynamic" 
217   mkFinalizer :: FinalizerPtr a -> Ptr a -> IO ()
218
219 foreignPtrFinalizer :: IORef [IO ()] -> IO ()
220 foreignPtrFinalizer r = do fs <- readIORef r; sequence_ fs
221
222 newForeignPtr_ :: Ptr a -> IO (ForeignPtr a)
223 -- ^Turns a plain memory reference into a foreign pointer that may be
224 -- associated with finalizers by using 'addForeignPtrFinalizer'.
225 newForeignPtr_ (Ptr obj) =  do
226   r <- newIORef []
227   return (ForeignPtr obj (PlainForeignPtr r))
228
229 touchForeignPtr :: ForeignPtr a -> IO ()
230 -- ^This function ensures that the foreign object in
231 -- question is alive at the given place in the sequence of IO
232 -- actions. In particular 'Foreign.ForeignPtr.withForeignPtr'
233 -- does a 'touchForeignPtr' after it
234 -- executes the user action.
235 -- 
236 -- Note that this function should not be used to express dependencies
237 -- between finalizers on 'ForeignPtr's.  For example, if the finalizer
238 -- for a 'ForeignPtr' @F1@ calls 'touchForeignPtr' on a second
239 -- 'ForeignPtr' @F2@, then the only guarantee is that the finalizer
240 -- for @F2@ is never started before the finalizer for @F1@.  They
241 -- might be started together if for example both @F1@ and @F2@ are
242 -- otherwise unreachable, and in that case the scheduler might end up
243 -- running the finalizer for @F2@ first.
244 --
245 -- In general, it is not recommended to use finalizers on separate
246 -- objects with ordering constraints between them.  To express the
247 -- ordering robustly requires explicit synchronisation using @MVar@s
248 -- between the finalizers, but even then the runtime sometimes runs
249 -- multiple finalizers sequentially in a single thread (for
250 -- performance reasons), so synchronisation between finalizers could
251 -- result in artificial deadlock.  Another alternative is to use
252 -- explicit reference counting.
253 --
254 touchForeignPtr (ForeignPtr fo r) = touch r
255
256 touch r = IO $ \s -> case touch# r s of s -> (# s, () #)
257
258 unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
259 -- ^This function extracts the pointer component of a foreign
260 -- pointer.  This is a potentially dangerous operations, as if the
261 -- argument to 'unsafeForeignPtrToPtr' is the last usage
262 -- occurrence of the given foreign pointer, then its finalizer(s) will
263 -- be run, which potentially invalidates the plain pointer just
264 -- obtained.  Hence, 'touchForeignPtr' must be used
265 -- wherever it has to be guaranteed that the pointer lives on - i.e.,
266 -- has another usage occurrence.
267 --
268 -- To avoid subtle coding errors, hand written marshalling code
269 -- should preferably use 'Foreign.ForeignPtr.withForeignPtr' rather
270 -- than combinations of 'unsafeForeignPtrToPtr' and
271 -- 'touchForeignPtr'.  However, the later routines
272 -- are occasionally preferred in tool generated marshalling code.
273 unsafeForeignPtrToPtr (ForeignPtr fo r) = Ptr fo
274
275 castForeignPtr :: ForeignPtr a -> ForeignPtr b
276 -- ^This function casts a 'ForeignPtr'
277 -- parameterised by one type into another type.
278 castForeignPtr f = unsafeCoerce# f
279
280 -- | Causes the finalizers associated with a foreign pointer to be run
281 -- immediately.
282 finalizeForeignPtr :: ForeignPtr a -> IO ()
283 finalizeForeignPtr (ForeignPtr _ foreignPtr) = do
284         finalizers <- readIORef refFinalizers
285         sequence_ finalizers
286         writeIORef refFinalizers []
287         where
288                 refFinalizers = case foreignPtr of
289                         (PlainForeignPtr ref) -> ref
290                         (MallocPtr  _ ref) -> ref