f182d193145027cb52c60501a2d392d999915c76
[ghc-base.git] / Foreign / Marshal / Pool.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 --------------------------------------------------------------------------------
3 -- |
4 -- Module      :  Foreign.Marshal.Pool
5 -- Copyright   :  (c) Sven Panne 2002-2004
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  sven.panne@aedion.de
9 -- Stability   :  provisional
10 -- Portability :  portable
11 --
12 -- This module contains support for pooled memory management. Under this scheme,
13 -- (re-)allocations belong to a given pool, and everything in a pool is
14 -- deallocated when the pool itself is deallocated. This is useful when
15 -- 'Foreign.Marshal.Alloc.alloca' with its implicit allocation and deallocation
16 -- is not flexible enough, but explicit uses of 'Foreign.Marshal.Alloc.malloc'
17 -- and 'free' are too awkward.
18 --
19 --------------------------------------------------------------------------------
20
21 module Foreign.Marshal.Pool (
22    -- * Pool management
23    Pool,
24    newPool,             -- :: IO Pool
25    freePool,            -- :: Pool -> IO ()
26    withPool,            -- :: (Pool -> IO b) -> IO b
27
28    -- * (Re-)Allocation within a pool
29    pooledMalloc,        -- :: Storable a => Pool                 -> IO (Ptr a)
30    pooledMallocBytes,   -- ::               Pool          -> Int -> IO (Ptr a)
31
32    pooledRealloc,       -- :: Storable a => Pool -> Ptr a        -> IO (Ptr a)
33    pooledReallocBytes,  -- ::               Pool -> Ptr a -> Int -> IO (Ptr a)
34
35    pooledMallocArray,   -- :: Storable a => Pool ->          Int -> IO (Ptr a)
36    pooledMallocArray0,  -- :: Storable a => Pool ->          Int -> IO (Ptr a)
37
38    pooledReallocArray,  -- :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
39    pooledReallocArray0, -- :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
40
41    -- * Combined allocation and marshalling
42    pooledNew,           -- :: Storable a => Pool -> a            -> IO (Ptr a)
43    pooledNewArray,      -- :: Storable a => Pool ->      [a]     -> IO (Ptr a)
44    pooledNewArray0      -- :: Storable a => Pool -> a -> [a]     -> IO (Ptr a)
45 ) where
46
47 #ifdef __GLASGOW_HASKELL__
48 import GHC.Base              ( Int, Monad(..), (.), not )
49 import GHC.Err               ( undefined )
50 import GHC.Exception         ( block, unblock, throw, catchException )
51 import GHC.IOBase            ( IO, IORef, newIORef, readIORef, writeIORef, )
52 import GHC.List              ( elem, length )
53 import GHC.Num               ( Num(..) )
54 #else
55 import Data.IORef            ( IORef, newIORef, readIORef, writeIORef )
56 #if defined(__NHC__)
57 import IO                    ( bracket )
58 #else
59 import Control.Exception     ( bracket )
60 #endif
61 #endif
62
63 import Control.Monad         ( liftM )
64 import Data.List             ( delete )
65 import Foreign.Marshal.Alloc ( mallocBytes, reallocBytes, free )
66 import Foreign.Marshal.Array ( pokeArray, pokeArray0 )
67 import Foreign.Marshal.Error ( throwIf )
68 import Foreign.Ptr           ( Ptr, castPtr )
69 import Foreign.Storable      ( Storable(sizeOf, poke) )
70
71 --------------------------------------------------------------------------------
72
73 -- To avoid non-H98 stuff like existentially quantified data constructors, we
74 -- simply use pointers to () below. Not very nice, but...
75
76 -- | A memory pool.
77
78 newtype Pool = Pool (IORef [Ptr ()])
79
80 -- | Allocate a fresh memory pool.
81
82 newPool :: IO Pool
83 newPool = liftM Pool (newIORef [])
84
85 -- | Deallocate a memory pool and everything which has been allocated in the
86 -- pool itself.
87
88 freePool :: Pool -> IO ()
89 freePool (Pool pool) = readIORef pool >>= freeAll
90    where freeAll []     = return ()
91          freeAll (p:ps) = free p >> freeAll ps
92
93 -- | Execute an action with a fresh memory pool, which gets automatically
94 -- deallocated (including its contents) after the action has finished.
95
96 withPool :: (Pool -> IO b) -> IO b
97 #ifdef __GLASGOW_HASKELL__
98 withPool act =   -- ATTENTION: cut-n-paste from Control.Exception below!
99    block (do
100       pool <- newPool
101       val <- catchException
102                 (unblock (act pool))
103                 (\e -> do freePool pool; throw e)
104       freePool pool
105       return val)
106 #else
107 withPool = bracket newPool freePool
108 #endif
109
110 --------------------------------------------------------------------------------
111
112 -- | Allocate space for storable type in the given pool. The size of the area
113 -- allocated is determined by the 'sizeOf' method from the instance of
114 -- 'Storable' for the appropriate type.
115
116 pooledMalloc :: Storable a => Pool -> IO (Ptr a)
117 pooledMalloc = pm undefined
118   where
119     pm           :: Storable a' => a' -> Pool -> IO (Ptr a')
120     pm dummy pool = pooledMallocBytes pool (sizeOf dummy)
121
122 -- | Allocate the given number of bytes of storage in the pool.
123
124 pooledMallocBytes :: Pool -> Int -> IO (Ptr a)
125 pooledMallocBytes (Pool pool) size = do
126    ptr <- mallocBytes size
127    ptrs <- readIORef pool
128    writeIORef pool (ptr:ptrs)
129    return (castPtr ptr)
130
131 -- | Adjust the storage area for an element in the pool to the given size of
132 -- the required type.
133
134 pooledRealloc :: Storable a => Pool -> Ptr a -> IO (Ptr a)
135 pooledRealloc = pr undefined
136   where
137     pr               :: Storable a' => a' -> Pool -> Ptr a' -> IO (Ptr a')
138     pr dummy pool ptr = pooledReallocBytes pool ptr (sizeOf dummy)
139
140 -- | Adjust the storage area for an element in the pool to the given size.
141
142 pooledReallocBytes :: Pool -> Ptr a -> Int -> IO (Ptr a)
143 pooledReallocBytes (Pool pool) ptr size = do
144    let cPtr = castPtr ptr
145    throwIf (not . (cPtr `elem`)) (\_ -> "pointer not in pool") (readIORef pool)
146    newPtr <- reallocBytes cPtr size
147    ptrs <- readIORef pool
148    writeIORef pool (newPtr : delete cPtr ptrs)
149    return (castPtr newPtr)
150
151 -- | Allocate storage for the given number of elements of a storable type in the
152 -- pool.
153
154 pooledMallocArray :: Storable a => Pool -> Int -> IO (Ptr a)
155 pooledMallocArray = pma undefined
156   where
157     pma                :: Storable a' => a' -> Pool -> Int -> IO (Ptr a')
158     pma dummy pool size = pooledMallocBytes pool (size * sizeOf dummy)
159
160 -- | Allocate storage for the given number of elements of a storable type in the
161 -- pool, but leave room for an extra element to signal the end of the array.
162
163 pooledMallocArray0 :: Storable a => Pool -> Int -> IO (Ptr a)
164 pooledMallocArray0 pool size =
165    pooledMallocArray pool (size + 1)
166
167 -- | Adjust the size of an array in the given pool.
168
169 pooledReallocArray :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
170 pooledReallocArray = pra undefined
171   where
172     pra                ::  Storable a' => a' -> Pool -> Ptr a' -> Int -> IO (Ptr a')
173     pra dummy pool ptr size  = pooledReallocBytes pool ptr (size * sizeOf dummy)
174
175 -- | Adjust the size of an array with an end marker in the given pool.
176
177 pooledReallocArray0 :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
178 pooledReallocArray0 pool ptr size =
179    pooledReallocArray pool ptr (size + 1)
180
181 --------------------------------------------------------------------------------
182
183 -- | Allocate storage for a value in the given pool and marshal the value into
184 -- this storage.
185
186 pooledNew :: Storable a => Pool -> a -> IO (Ptr a)
187 pooledNew pool val = do
188    ptr <- pooledMalloc pool
189    poke ptr val
190    return ptr
191
192 -- | Allocate consecutive storage for a list of values in the given pool and
193 -- marshal these values into it.
194
195 pooledNewArray :: Storable a => Pool -> [a] -> IO (Ptr a)
196 pooledNewArray pool vals = do
197    ptr <- pooledMallocArray pool (length vals)
198    pokeArray ptr vals
199    return ptr
200
201 -- | Allocate consecutive storage for a list of values in the given pool and
202 -- marshal these values into it, terminating the end with the given marker.
203
204 pooledNewArray0 :: Storable a => Pool -> a -> [a] -> IO (Ptr a)
205 pooledNewArray0 pool marker vals = do
206    ptr <- pooledMallocArray0 pool (length vals)
207    pokeArray0 marker ptr vals
208    return ptr