ce167b5912d55e601828f94d7abdff8788987b02
[ghc-base.git] / Foreign / Marshal / Alloc.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
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 -- Marshalling support: basic routines for memory allocation
13 --
14 -----------------------------------------------------------------------------
15
16 module Foreign.Marshal.Alloc (
17   -- * Allocation
18   malloc,       -- :: Storable a =>        IO (Ptr a)
19   mallocBytes,  -- ::               Int -> IO (Ptr a)
20
21   alloca,       -- :: Storable a =>        (Ptr a -> IO b) -> IO b
22   allocaBytes,  -- ::               Int -> (Ptr a -> IO b) -> IO b
23
24   realloc,      -- :: Storable b => Ptr a        -> IO (Ptr b)
25   reallocBytes, -- ::               Ptr a -> Int -> IO (Ptr a)
26
27 #ifdef __HUGS__
28   free,         -- :: Ptr a -> IO ()
29   finalizerFree -- :: FunPtr (Ptr a -> IO ())
30 #else
31   free          -- :: Ptr a -> IO ()
32 #endif
33 ) where
34
35 import Data.Maybe
36 import Foreign.Ptr              ( Ptr, nullPtr, FunPtr )
37 import Foreign.C.TypesISO       ( CSize )
38 import Foreign.Storable         ( Storable(sizeOf) )
39
40 #ifdef __GLASGOW_HASKELL__
41 import GHC.Exception            ( bracket )
42 import GHC.IOBase
43 import GHC.Real
44 import GHC.Ptr
45 import GHC.Err
46 import GHC.Base
47 #else
48 import Control.Exception        ( bracket )
49 #endif
50
51
52 -- exported functions
53 -- ------------------
54
55 -- |Allocate space for storable type.  The size of the area allocated
56 -- is determined by the 'sizeOf' method from the instance of
57 -- 'Storable' for the appropriate type.
58 --
59 malloc :: Storable a => IO (Ptr a)
60 malloc  = doMalloc undefined
61   where
62     doMalloc       :: Storable a => a -> IO (Ptr a)
63     doMalloc dummy  = mallocBytes (sizeOf dummy)
64
65 -- |Allocate given number of bytes of storage, equivalent to C\'s @malloc()@.
66 --
67 mallocBytes      :: Int -> IO (Ptr a)
68 mallocBytes size  = failWhenNULL "malloc" (_malloc (fromIntegral size))
69
70 -- |Temporarily allocate space for a storable type.
71 --
72 -- * the pointer passed as an argument to the function must /not/ escape from
73 --   this function; in other words, in @alloca f@ the allocated storage must
74 --   not be used after @f@ returns
75 --
76 alloca :: Storable a => (Ptr a -> IO b) -> IO b
77 alloca  = doAlloca undefined
78   where
79     doAlloca       :: Storable a => a -> (Ptr a -> IO b) -> IO b
80     doAlloca dummy  = allocaBytes (sizeOf dummy)
81
82 -- |Temporarily allocate the given number of bytes of storage.
83 --
84 -- * the pointer passed as an argument to the function must /not/ escape from
85 --   this function; in other words, in @allocaBytes n f@ the allocated storage
86 --   must not be used after @f@ returns
87 --
88 #ifdef __GLASGOW_HASKELL__
89 allocaBytes :: Int -> (Ptr a -> IO b) -> IO b
90 allocaBytes (I# size) action = IO $ \ s ->
91      case newPinnedByteArray# size s      of { (# s, mbarr# #) ->
92      case unsafeFreezeByteArray# mbarr# s of { (# s, barr#  #) ->
93      let addr = Ptr (byteArrayContents# barr#) in
94      case action addr    of { IO action ->
95      case action s       of { (# s, r #) ->
96      case touch# barr# s of { s ->
97      (# s, r #)
98   }}}}}
99 #else
100 allocaBytes      :: Int -> (Ptr a -> IO b) -> IO b
101 allocaBytes size  = bracket (mallocBytes size) free
102 #endif
103
104 -- |Adjust a malloc\'ed storage area to the given size of the required type
105 -- (corresponds to C\'s @realloc()@).
106 --
107 realloc :: Storable b => Ptr a -> IO (Ptr b)
108 realloc  = doRealloc undefined
109   where
110     doRealloc           :: Storable b => b -> Ptr a -> IO (Ptr b)
111     doRealloc dummy ptr  = let
112                              size = fromIntegral (sizeOf dummy)
113                            in
114                            failWhenNULL "realloc" (_realloc ptr size)
115
116 -- |Adjust a malloc\'ed storage area to the given size (equivalent to
117 -- C\'s @realloc()@).
118 --
119 reallocBytes          :: Ptr a -> Int -> IO (Ptr a)
120 reallocBytes ptr size  = 
121   failWhenNULL "realloc" (_realloc ptr (fromIntegral size))
122
123 -- |Free malloc\'ed storage (equivalent to
124 -- C\'s @free()@)
125 --
126 free :: Ptr a -> IO ()
127 free  = _free
128
129
130 -- auxilliary routines
131 -- -------------------
132
133 -- asserts that the pointer returned from the action in the second argument is
134 -- non-null
135 --
136 failWhenNULL :: String -> IO (Ptr a) -> IO (Ptr a)
137 failWhenNULL name f = do
138    addr <- f
139    if addr == nullPtr
140 #ifdef __GLASGOW_HASKELL__
141       then ioException (IOError Nothing ResourceExhausted name 
142                                         "out of memory" Nothing)
143 #else
144       then ioError (userError (name++": out of memory"))
145 #endif
146       else return addr
147
148 -- basic C routines needed for memory allocation
149 --
150 foreign import ccall unsafe "stdlib.h malloc"  _malloc  ::          CSize -> IO (Ptr a)
151 foreign import ccall unsafe "stdlib.h realloc" _realloc :: Ptr a -> CSize -> IO (Ptr b)
152 foreign import ccall unsafe "stdlib.h free"    _free    :: Ptr a -> IO ()
153 #ifdef __HUGS__
154 -- |A pointer to a foreign function equivalent to @free@, which may be used
155 -- as a finalizer for storage allocated with @malloc@ or @mallocBytes@.
156 foreign import ccall unsafe "stdlib.h &free"
157                         finalizerFree :: FunPtr (Ptr a -> IO ())
158 #endif