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