export allocaBytesAligned; make allocaArray use the correct alignment (#2917)
[ghc-base.git] / Foreign / Marshal / Alloc.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Foreign.Marshal.Alloc
5 -- Copyright   :  (c) The FFI task force 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 module "Foreign.Marshal.Alloc" provides operations to allocate and
13 -- deallocate blocks of raw memory (i.e., unstructured chunks of memory
14 -- outside of the area maintained by the Haskell storage manager).  These
15 -- memory blocks are commonly used to pass compound data structures to
16 -- foreign functions or to provide space in which compound result values
17 -- are obtained from foreign functions.
18 -- 
19 -- If any of the allocation functions fails, a value of 'nullPtr' is
20 -- produced.  If 'free' or 'reallocBytes' is applied to a memory area
21 -- that has been allocated with 'alloca' or 'allocaBytes', the
22 -- behaviour is undefined.  Any further access to memory areas allocated with
23 -- 'alloca' or 'allocaBytes', after the computation that was passed to
24 -- the allocation function has terminated, leads to undefined behaviour.  Any
25 -- further access to the memory area referenced by a pointer passed to
26 -- 'realloc', 'reallocBytes', or 'free' entails undefined
27 -- behaviour.
28 -- 
29 -- All storage allocated by functions that allocate based on a /size in bytes/
30 -- must be sufficiently aligned for any of the basic foreign types
31 -- that fits into the newly allocated storage. All storage allocated by
32 -- functions that allocate based on a specific type must be sufficiently
33 -- aligned for that type. Array allocation routines need to obey the same
34 -- alignment constraints for each array element.
35 --
36 -----------------------------------------------------------------------------
37
38 module Foreign.Marshal.Alloc (
39   -- * Memory allocation
40   -- ** Local allocation
41   alloca,       -- :: Storable a =>        (Ptr a -> IO b) -> IO b
42   allocaBytes,  -- ::               Int -> (Ptr a -> IO b) -> IO b
43   allocaBytesAligned,  -- ::        Int -> Int -> (Ptr a -> IO b) -> IO b
44
45   -- ** Dynamic allocation
46   malloc,       -- :: Storable a =>        IO (Ptr a)
47   mallocBytes,  -- ::               Int -> IO (Ptr a)
48
49   realloc,      -- :: Storable b => Ptr a        -> IO (Ptr b)
50   reallocBytes, -- ::               Ptr a -> Int -> IO (Ptr a)
51
52   free,         -- :: Ptr a -> IO ()
53   finalizerFree -- :: FinalizerPtr a
54 ) where
55
56 import Data.Maybe
57 import Foreign.C.Types          ( CSize )
58 import Foreign.Storable         ( Storable(sizeOf,alignment) )
59
60 #ifndef __GLASGOW_HASKELL__
61 import Foreign.Ptr              ( Ptr, nullPtr, FunPtr )
62 #endif
63
64 #ifdef __GLASGOW_HASKELL__
65 import Foreign.ForeignPtr       ( FinalizerPtr )
66 import GHC.IO.Exception
67 import GHC.Real
68 import GHC.Ptr
69 import GHC.Err
70 import GHC.Base
71 import GHC.Num
72 #elif defined(__NHC__)
73 import NHC.FFI                  ( FinalizerPtr, CInt(..) )
74 import IO                       ( bracket )
75 #else
76 import Control.Exception.Base   ( bracket )
77 #endif
78
79 #ifdef __HUGS__
80 import Hugs.Prelude             ( IOException(IOError),
81                                   IOErrorType(ResourceExhausted) )
82 import Hugs.ForeignPtr          ( FinalizerPtr )
83 #endif
84
85
86 -- exported functions
87 -- ------------------
88
89 -- |Allocate a block of memory that is sufficient to hold values of type
90 -- @a@.  The size of the area allocated is determined by the 'sizeOf'
91 -- method from the instance of 'Storable' for the appropriate type.
92 --
93 -- The memory may be deallocated using 'free' or 'finalizerFree' when
94 -- no longer required.
95 --
96 {-# INLINE malloc #-}
97 malloc :: Storable a => IO (Ptr a)
98 malloc  = doMalloc undefined
99   where
100     doMalloc       :: Storable b => b -> IO (Ptr b)
101     doMalloc dummy  = mallocBytes (sizeOf dummy)
102
103 -- |Allocate a block of memory of the given number of bytes.
104 -- The block of memory is sufficiently aligned for any of the basic
105 -- foreign types that fits into a memory block of the allocated size.
106 --
107 -- The memory may be deallocated using 'free' or 'finalizerFree' when
108 -- no longer required.
109 --
110 mallocBytes      :: Int -> IO (Ptr a)
111 mallocBytes size  = failWhenNULL "malloc" (_malloc (fromIntegral size))
112
113 -- |@'alloca' f@ executes the computation @f@, passing as argument
114 -- a pointer to a temporarily allocated block of memory sufficient to
115 -- hold values of type @a@.
116 --
117 -- The memory is freed when @f@ terminates (either normally or via an
118 -- exception), so the pointer passed to @f@ must /not/ be used after this.
119 --
120 {-# INLINE alloca #-}
121 alloca :: Storable a => (Ptr a -> IO b) -> IO b
122 alloca  = doAlloca undefined
123   where
124     doAlloca       :: Storable a' => a' -> (Ptr a' -> IO b') -> IO b'
125     doAlloca dummy  = allocaBytesAligned (sizeOf dummy) (alignment dummy)
126
127 -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument
128 -- a pointer to a temporarily allocated block of memory of @n@ bytes.
129 -- The block of memory is sufficiently aligned for any of the basic
130 -- foreign types that fits into a memory block of the allocated size.
131 --
132 -- The memory is freed when @f@ terminates (either normally or via an
133 -- exception), so the pointer passed to @f@ must /not/ be used after this.
134 --
135 #ifdef __GLASGOW_HASKELL__
136 allocaBytes :: Int -> (Ptr a -> IO b) -> IO b
137 allocaBytes (I# size) action = IO $ \ s0 ->
138      case newPinnedByteArray# size s0      of { (# s1, mbarr# #) ->
139      case unsafeFreezeByteArray# mbarr# s1 of { (# s2, barr#  #) ->
140      let addr = Ptr (byteArrayContents# barr#) in
141      case action addr     of { IO action' ->
142      case action' s2      of { (# s3, r #) ->
143      case touch# barr# s3 of { s4 ->
144      (# s4, r #)
145   }}}}}
146
147 allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b
148 allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 ->
149      case newAlignedPinnedByteArray# size align s0 of { (# s1, mbarr# #) ->
150      case unsafeFreezeByteArray# mbarr# s1 of { (# s2, barr#  #) ->
151      let addr = Ptr (byteArrayContents# barr#) in
152      case action addr     of { IO action' ->
153      case action' s2      of { (# s3, r #) ->
154      case touch# barr# s3 of { s4 ->
155      (# s4, r #)
156   }}}}}
157 #else
158 allocaBytes      :: Int -> (Ptr a -> IO b) -> IO b
159 allocaBytes size  = bracket (mallocBytes size) free
160
161 allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b
162 allocaBytesAligned size align = allocaBytes size -- wrong
163 #endif
164
165 -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes'
166 -- to the size needed to store values of type @b@.  The returned pointer
167 -- may refer to an entirely different memory area, but will be suitably
168 -- aligned to hold values of type @b@.  The contents of the referenced
169 -- memory area will be the same as of the original pointer up to the
170 -- minimum of the original size and the size of values of type @b@.
171 --
172 -- If the argument to 'realloc' is 'nullPtr', 'realloc' behaves like
173 -- 'malloc'.
174 --
175 realloc :: Storable b => Ptr a -> IO (Ptr b)
176 realloc  = doRealloc undefined
177   where
178     doRealloc           :: Storable b' => b' -> Ptr a' -> IO (Ptr b')
179     doRealloc dummy ptr  = let
180                              size = fromIntegral (sizeOf dummy)
181                            in
182                            failWhenNULL "realloc" (_realloc ptr size)
183
184 -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes'
185 -- to the given size.  The returned pointer may refer to an entirely
186 -- different memory area, but will be sufficiently aligned for any of the
187 -- basic foreign types that fits into a memory block of the given size.
188 -- The contents of the referenced memory area will be the same as of
189 -- the original pointer up to the minimum of the original size and the
190 -- given size.
191 --
192 -- If the pointer argument to 'reallocBytes' is 'nullPtr', 'reallocBytes'
193 -- behaves like 'malloc'.  If the requested size is 0, 'reallocBytes'
194 -- behaves like 'free'.
195 --
196 reallocBytes          :: Ptr a -> Int -> IO (Ptr a)
197 reallocBytes ptr 0     = do free ptr; return nullPtr
198 reallocBytes ptr size  = 
199   failWhenNULL "realloc" (_realloc ptr (fromIntegral size))
200
201 -- |Free a block of memory that was allocated with 'malloc',
202 -- 'mallocBytes', 'realloc', 'reallocBytes', 'Foreign.Marshal.Utils.new'
203 -- or any of the @new@/X/ functions in "Foreign.Marshal.Array" or
204 -- "Foreign.C.String".
205 --
206 free :: Ptr a -> IO ()
207 free  = _free
208
209
210 -- auxilliary routines
211 -- -------------------
212
213 -- asserts that the pointer returned from the action in the second argument is
214 -- non-null
215 --
216 failWhenNULL :: String -> IO (Ptr a) -> IO (Ptr a)
217 failWhenNULL name f = do
218    addr <- f
219    if addr == nullPtr
220 #if __GLASGOW_HASKELL__
221       then ioError (IOError Nothing ResourceExhausted name 
222                                         "out of memory" Nothing Nothing)
223 #elif __HUGS__
224       then ioError (IOError Nothing ResourceExhausted name 
225                                         "out of memory" Nothing)
226 #else
227       then ioError (userError (name++": out of memory"))
228 #endif
229       else return addr
230
231 -- basic C routines needed for memory allocation
232 --
233 foreign import ccall unsafe "stdlib.h malloc"  _malloc  ::          CSize -> IO (Ptr a)
234 foreign import ccall unsafe "stdlib.h realloc" _realloc :: Ptr a -> CSize -> IO (Ptr b)
235 foreign import ccall unsafe "stdlib.h free"    _free    :: Ptr a -> IO ()
236
237 -- | A pointer to a foreign function equivalent to 'free', which may be
238 -- used as a finalizer (cf 'Foreign.ForeignPtr.ForeignPtr') for storage
239 -- allocated with 'malloc', 'mallocBytes', 'realloc' or 'reallocBytes'.
240 foreign import ccall unsafe "stdlib.h &free" finalizerFree :: FinalizerPtr a