f15d048a9518b13a2cdb2f0f82d311a993e47f5a
[ghc-base.git] / Foreign / Marshal / Pool.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
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         ( throw )
51 import GHC.IO                ( IO, mask, catchAny )
52 import GHC.IORef             ( IORef, newIORef, readIORef, writeIORef )
53 import GHC.List              ( elem, length )
54 import GHC.Num               ( Num(..) )
55 #else
56 import Data.IORef            ( IORef, newIORef, readIORef, writeIORef )
57 #if defined(__NHC__)
58 import IO                    ( bracket )
59 #else
60 import Control.Exception.Base ( bracket )
61 #endif
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 #ifdef __GLASGOW_HASKELL__
99 withPool act =   -- ATTENTION: cut-n-paste from Control.Exception below!
100    mask (\restore -> do
101       pool <- newPool
102       val <- catchAny
103                 (restore (act pool))
104                 (\e -> do freePool pool; throw e)
105       freePool pool
106       return val)
107 #else
108 withPool = bracket newPool freePool
109 #endif
110
111 --------------------------------------------------------------------------------
112
113 -- | Allocate space for storable type in the given pool. The size of the area
114 -- allocated is determined by the 'sizeOf' method from the instance of
115 -- 'Storable' for the appropriate type.
116
117 pooledMalloc :: Storable a => Pool -> IO (Ptr a)
118 pooledMalloc = pm undefined
119   where
120     pm           :: Storable a' => a' -> Pool -> IO (Ptr a')
121     pm dummy pool = pooledMallocBytes pool (sizeOf dummy)
122
123 -- | Allocate the given number of bytes of storage in the pool.
124
125 pooledMallocBytes :: Pool -> Int -> IO (Ptr a)
126 pooledMallocBytes (Pool pool) size = do
127    ptr <- mallocBytes size
128    ptrs <- readIORef pool
129    writeIORef pool (ptr:ptrs)
130    return (castPtr ptr)
131
132 -- | Adjust the storage area for an element in the pool to the given size of
133 -- the required type.
134
135 pooledRealloc :: Storable a => Pool -> Ptr a -> IO (Ptr a)
136 pooledRealloc = pr undefined
137   where
138     pr               :: Storable a' => a' -> Pool -> Ptr a' -> IO (Ptr a')
139     pr dummy pool ptr = pooledReallocBytes pool ptr (sizeOf dummy)
140
141 -- | Adjust the storage area for an element in the pool to the given size.
142
143 pooledReallocBytes :: Pool -> Ptr a -> Int -> IO (Ptr a)
144 pooledReallocBytes (Pool pool) ptr size = do
145    let cPtr = castPtr ptr
146    _ <- throwIf (not . (cPtr `elem`)) (\_ -> "pointer not in pool") (readIORef pool)
147    newPtr <- reallocBytes cPtr size
148    ptrs <- readIORef pool
149    writeIORef pool (newPtr : delete cPtr ptrs)
150    return (castPtr newPtr)
151
152 -- | Allocate storage for the given number of elements of a storable type in the
153 -- pool.
154
155 pooledMallocArray :: Storable a => Pool -> Int -> IO (Ptr a)
156 pooledMallocArray = pma undefined
157   where
158     pma                :: Storable a' => a' -> Pool -> Int -> IO (Ptr a')
159     pma dummy pool size = pooledMallocBytes pool (size * sizeOf dummy)
160
161 -- | Allocate storage for the given number of elements of a storable type in the
162 -- pool, but leave room for an extra element to signal the end of the array.
163
164 pooledMallocArray0 :: Storable a => Pool -> Int -> IO (Ptr a)
165 pooledMallocArray0 pool size =
166    pooledMallocArray pool (size + 1)
167
168 -- | Adjust the size of an array in the given pool.
169
170 pooledReallocArray :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
171 pooledReallocArray = pra undefined
172   where
173     pra                ::  Storable a' => a' -> Pool -> Ptr a' -> Int -> IO (Ptr a')
174     pra dummy pool ptr size  = pooledReallocBytes pool ptr (size * sizeOf dummy)
175
176 -- | Adjust the size of an array with an end marker in the given pool.
177
178 pooledReallocArray0 :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
179 pooledReallocArray0 pool ptr size =
180    pooledReallocArray pool ptr (size + 1)
181
182 --------------------------------------------------------------------------------
183
184 -- | Allocate storage for a value in the given pool and marshal the value into
185 -- this storage.
186
187 pooledNew :: Storable a => Pool -> a -> IO (Ptr a)
188 pooledNew pool val = do
189    ptr <- pooledMalloc pool
190    poke ptr val
191    return ptr
192
193 -- | Allocate consecutive storage for a list of values in the given pool and
194 -- marshal these values into it.
195
196 pooledNewArray :: Storable a => Pool -> [a] -> IO (Ptr a)
197 pooledNewArray pool vals = do
198    ptr <- pooledMallocArray pool (length vals)
199    pokeArray ptr vals
200    return ptr
201
202 -- | Allocate consecutive storage for a list of values in the given pool and
203 -- marshal these values into it, terminating the end with the given marker.
204
205 pooledNewArray0 :: Storable a => Pool -> a -> [a] -> IO (Ptr a)
206 pooledNewArray0 pool marker vals = do
207    ptr <- pooledMallocArray0 pool (length vals)
208    pokeArray0 marker ptr vals
209    return ptr