Adjust behaviour of gcd
[ghc-base.git] / Foreign / ForeignPtr.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Foreign.ForeignPtr
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  ffi@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  portable
12 --
13 -- The 'ForeignPtr' type and operations.  This module is part of the
14 -- Foreign Function Interface (FFI) and will usually be imported via
15 -- the "Foreign" module.
16 --
17 -----------------------------------------------------------------------------
18
19 module Foreign.ForeignPtr
20         ( 
21         -- * Finalised data pointers
22           ForeignPtr
23         , FinalizerPtr
24 #if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
25         , FinalizerEnvPtr
26 #endif
27         -- ** Basic operations
28         , newForeignPtr
29         , newForeignPtr_
30         , addForeignPtrFinalizer
31 #if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
32         , newForeignPtrEnv
33         , addForeignPtrFinalizerEnv
34 #endif
35         , withForeignPtr
36
37 #ifdef __GLASGOW_HASKELL__
38         , finalizeForeignPtr
39 #endif
40
41         -- ** Low-level operations
42         , unsafeForeignPtrToPtr
43         , touchForeignPtr
44         , castForeignPtr
45
46         -- ** Allocating managed memory
47         , mallocForeignPtr
48         , mallocForeignPtrBytes
49         , mallocForeignPtrArray
50         , mallocForeignPtrArray0
51         ) 
52         where
53
54 import Foreign.Ptr
55
56 #ifdef __NHC__
57 import NHC.FFI
58   ( ForeignPtr
59   , FinalizerPtr
60   , newForeignPtr
61   , newForeignPtr_
62   , addForeignPtrFinalizer
63   , withForeignPtr
64   , unsafeForeignPtrToPtr
65   , touchForeignPtr
66   , castForeignPtr
67   , Storable(sizeOf)
68   , malloc, mallocBytes, finalizerFree
69   )
70 #endif
71
72 #ifdef __HUGS__
73 import Hugs.ForeignPtr
74 #endif
75
76 #ifndef __NHC__
77 import Foreign.Storable ( Storable(sizeOf) )
78 #endif
79
80 #ifdef __GLASGOW_HASKELL__
81 import GHC.Base
82 -- import GHC.IO
83 import GHC.Num
84 import GHC.Err          ( undefined )
85 import GHC.ForeignPtr
86 #endif
87
88 #if !defined(__NHC__) && !defined(__GLASGOW_HASKELL__)
89 import Foreign.Marshal.Alloc    ( malloc, mallocBytes, finalizerFree )
90
91 instance Eq (ForeignPtr a) where 
92     p == q  =  unsafeForeignPtrToPtr p == unsafeForeignPtrToPtr q
93
94 instance Ord (ForeignPtr a) where 
95     compare p q  =  compare (unsafeForeignPtrToPtr p) (unsafeForeignPtrToPtr q)
96
97 instance Show (ForeignPtr a) where
98     showsPrec p f = showsPrec p (unsafeForeignPtrToPtr f)
99 #endif
100
101
102 #ifndef __NHC__
103 newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
104 -- ^Turns a plain memory reference into a foreign pointer, and
105 -- associates a finalizer with the reference.  The finalizer will be
106 -- executed after the last reference to the foreign object is dropped.
107 -- There is no guarantee of promptness, however the finalizer will be
108 -- executed before the program exits.
109 newForeignPtr finalizer p
110   = do fObj <- newForeignPtr_ p
111        addForeignPtrFinalizer finalizer fObj
112        return fObj
113
114 withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
115 -- ^This is a way to look at the pointer living inside a
116 -- foreign object.  This function takes a function which is
117 -- applied to that pointer. The resulting 'IO' action is then
118 -- executed. The foreign object is kept alive at least during
119 -- the whole action, even if it is not used directly
120 -- inside. Note that it is not safe to return the pointer from
121 -- the action and use it after the action completes. All uses
122 -- of the pointer should be inside the
123 -- 'withForeignPtr' bracket.  The reason for
124 -- this unsafeness is the same as for
125 -- 'unsafeForeignPtrToPtr' below: the finalizer
126 -- may run earlier than expected, because the compiler can only
127 -- track usage of the 'ForeignPtr' object, not
128 -- a 'Ptr' object made from it.
129 --
130 -- This function is normally used for marshalling data to
131 -- or from the object pointed to by the
132 -- 'ForeignPtr', using the operations from the
133 -- 'Storable' class.
134 withForeignPtr fo io
135   = do r <- io (unsafeForeignPtrToPtr fo)
136        touchForeignPtr fo
137        return r
138 #endif /* ! __NHC__ */
139
140 #if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
141 -- | This variant of 'newForeignPtr' adds a finalizer that expects an
142 -- environment in addition to the finalized pointer.  The environment
143 -- that will be passed to the finalizer is fixed by the second argument to
144 -- 'newForeignPtrEnv'.
145 newForeignPtrEnv ::
146     FinalizerEnvPtr env a -> Ptr env -> Ptr a -> IO (ForeignPtr a)
147 newForeignPtrEnv finalizer env p
148   = do fObj <- newForeignPtr_ p
149        addForeignPtrFinalizerEnv finalizer env fObj
150        return fObj
151 #endif /* __HUGS__ */
152
153 #ifndef __GLASGOW_HASKELL__
154 mallocForeignPtr :: Storable a => IO (ForeignPtr a)
155 mallocForeignPtr = do
156   r <- malloc
157   newForeignPtr finalizerFree r
158
159 mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
160 mallocForeignPtrBytes n = do
161   r <- mallocBytes n
162   newForeignPtr finalizerFree r
163 #endif /* !__GLASGOW_HASKELL__ */
164
165 -- | This function is similar to 'Foreign.Marshal.Array.mallocArray',
166 -- but yields a memory area that has a finalizer attached that releases
167 -- the memory area.  As with 'mallocForeignPtr', it is not guaranteed that
168 -- the block of memory was allocated by 'Foreign.Marshal.Alloc.malloc'.
169 mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a)
170 mallocForeignPtrArray  = doMalloc undefined
171   where
172     doMalloc            :: Storable b => b -> Int -> IO (ForeignPtr b)
173     doMalloc dummy size  = mallocForeignPtrBytes (size * sizeOf dummy)
174
175 -- | This function is similar to 'Foreign.Marshal.Array.mallocArray0',
176 -- but yields a memory area that has a finalizer attached that releases
177 -- the memory area.  As with 'mallocForeignPtr', it is not guaranteed that
178 -- the block of memory was allocated by 'Foreign.Marshal.Alloc.malloc'.
179 mallocForeignPtrArray0      :: Storable a => Int -> IO (ForeignPtr a)
180 mallocForeignPtrArray0 size  = mallocForeignPtrArray (size + 1)