[project @ 2003-01-28 21:38:30 by panne]
[ghc-base.git] / Foreign / Marshal / Pool.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 --------------------------------------------------------------------------------
3 -- |
4 -- Module      :  Foreign.Marshal.Pool
5 -- Copyright   :  (c) Sven Panne 2003
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  sven_panne@yahoo.com
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 #if defined(__NHC__)
48 import IO                    ( bracket )
49 #elif defined(__HUGS__)
50 import Control.Exception     ( bracket )
51 #endif
52
53 #ifdef __GLASGOW_HASKELL__
54 import GHC.Base              ( Int, Monad(..), (.), not, map )
55 import GHC.Err               ( undefined )
56 import GHC.Exception         ( block, unblock, throw, catchException )
57 import GHC.IOBase            ( IO, IORef, newIORef, readIORef, writeIORef, )
58 import GHC.List              ( elem, length )
59 import GHC.Num               ( Num(..) )
60 #else
61 import Data.IORef            ( IORef, newIORef, readIORef, modifyIORef )
62 #endif
63
64 import Control.Monad         ( liftM )
65 import Data.List             ( delete )
66 import Foreign.Marshal.Alloc ( mallocBytes, reallocBytes, free )
67 import Foreign.Marshal.Array ( pokeArray, pokeArray0 )
68 import Foreign.Marshal.Error ( throwIf )
69 import Foreign.Ptr           ( Ptr, castPtr )
70 import Foreign.Storable      ( Storable(sizeOf, poke) )
71
72 --------------------------------------------------------------------------------
73
74 -- To avoid non-H98 stuff like existentially quantified data constructors, we
75 -- simply use pointers to () below. Not very nice, but...
76
77 -- | A memory pool.
78
79 newtype Pool = Pool (IORef [Ptr ()])
80
81 -- | Allocate a fresh memory pool.
82
83 newPool :: IO Pool
84 newPool = liftM Pool (newIORef [])
85
86 -- | Deallocate a memory pool and everything which has been allocated in the
87 -- pool itself.
88
89 freePool :: Pool -> IO ()
90 freePool (Pool pool) = readIORef pool >>= freeAll
91    where freeAll []     = return ()
92          freeAll (p:ps) = free p >> freeAll ps
93
94 -- | Execute an action with a fresh memory pool, which gets automatically
95 -- deallocated (including its contents) after the action has finished.
96
97 withPool :: (Pool -> IO b) -> IO b
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
107 --------------------------------------------------------------------------------
108
109 -- | Allocate space for storable type in the given pool. The size of the area
110 -- allocated is determined by the 'sizeOf' method from the instance of
111 -- 'Storable' for the appropriate type.
112
113 pooledMalloc :: Storable a => Pool -> IO (Ptr a)
114 pooledMalloc = pm undefined
115   where
116     pm           :: Storable a => a -> Pool -> IO (Ptr a)
117     pm dummy pool = pooledMallocBytes pool (sizeOf dummy)
118
119 -- | Allocate the given number of bytes of storage in the pool.
120
121 pooledMallocBytes :: Pool -> Int -> IO (Ptr a)
122 pooledMallocBytes (Pool pool) size = do
123    ptr <- mallocBytes size
124    ptrs <- readIORef pool
125    writeIORef pool (ptr:ptrs)
126    return (castPtr ptr)
127
128 -- | Adjust the storage area for an element in the pool to the given size of
129 -- the required type.
130
131 pooledRealloc :: Storable a => Pool -> Ptr a -> IO (Ptr a)
132 pooledRealloc = pr undefined
133   where
134     pr               :: Storable a => a -> Pool -> Ptr a -> IO (Ptr a)
135     pr dummy pool ptr = pooledReallocBytes pool ptr (sizeOf dummy)
136
137 -- | Adjust the storage area for an element in the pool to the given size.
138
139 pooledReallocBytes :: Pool -> Ptr a -> Int -> IO (Ptr a)
140 pooledReallocBytes (Pool pool) ptr size = do
141    let cPtr = castPtr ptr
142    throwIf (not . (cPtr `elem`)) (\_ -> "pointer not in pool") (readIORef pool)
143    newPtr <- reallocBytes cPtr size
144    ptrs <- readIORef pool
145    writeIORef pool (newPtr : delete cPtr ptrs)
146    return (castPtr newPtr)
147
148 -- | Allocate storage for the given number of elements of a storable type in the
149 -- pool.
150
151 pooledMallocArray :: Storable a => Pool -> Int -> IO (Ptr a)
152 pooledMallocArray = pma undefined
153   where
154     pma                :: Storable a => a -> Pool -> Int -> IO (Ptr a)
155     pma dummy pool size = pooledMallocBytes pool (size * sizeOf dummy)
156
157 -- | Allocate storage for the given number of elements of a storable type in the
158 -- pool, but leave room for an extra element to signal the end of the array.
159
160 pooledMallocArray0 :: Storable a => Pool -> Int -> IO (Ptr a)
161 pooledMallocArray0 pool size =
162    pooledMallocArray pool (size + 1)
163
164 -- | Adjust the size of an array in the given pool.
165
166 pooledReallocArray :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
167 pooledReallocArray = pra undefined
168   where
169     pra                ::  Storable a => a -> Pool -> Ptr a -> Int -> IO (Ptr a)
170     pra dummy pool ptr size  = pooledReallocBytes pool ptr (size * sizeOf dummy)
171
172 -- | Adjust the size of an array with an end marker in the given pool.
173
174 pooledReallocArray0 :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
175 pooledReallocArray0 pool ptr size =
176    pooledReallocArray pool ptr (size + 1)
177
178 --------------------------------------------------------------------------------
179
180 -- | Allocate storage for a value in the given pool and marshal the value into
181 -- this storage.
182
183 pooledNew :: Storable a => Pool -> a -> IO (Ptr a)
184 pooledNew pool val = do
185    ptr <- pooledMalloc pool
186    poke ptr val
187    return ptr
188
189 -- | Allocate consecutive storage for a list of values in the given pool and
190 -- marshal these values into it.
191
192 pooledNewArray :: Storable a => Pool -> [a] -> IO (Ptr a)
193 pooledNewArray pool vals = do
194    ptr <- pooledMallocArray pool (length vals)
195    pokeArray ptr vals
196    return ptr
197
198 -- | Allocate consecutive storage for a list of values in the given pool and
199 -- marshal these values into it, terminating the end with the given marker.
200
201 pooledNewArray0 :: Storable a => Pool -> a -> [a] -> IO (Ptr a)
202 pooledNewArray0 pool marker vals = do
203    ptr <- pooledMallocArray0 pool (length vals)
204    pokeArray0 marker ptr vals
205    return ptr