002961e47b597a580b1acc636a4d044a0437a463
[ghc-base.git] / Foreign / Marshal / Array.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Foreign.Marshal.Array
5 -- Copyright   :  (c) The FFI task force 2001
6 -- License     :  BSD-style (see the file libraries/core/LICENSE)
7 -- 
8 -- Maintainer  :  ffi@haskell.org
9 -- Stability   :  provisional
10 -- Portability :  portable
11 --
12 -- Marshalling support: routines allocating, storing, and retrieving Haskell
13 -- lists that are represented as arrays in the foreign language
14 --
15 -----------------------------------------------------------------------------
16
17 module Foreign.Marshal.Array (
18   -- * Marshalling arrays
19
20   -- ** Allocation
21   --
22   mallocArray,    -- :: Storable a => Int -> IO (Ptr a)
23   mallocArray0,   -- :: Storable a => Int -> IO (Ptr a)
24
25   allocaArray,    -- :: Storable a => Int -> (Ptr a -> IO b) -> IO b
26   allocaArray0,   -- :: Storable a => Int -> (Ptr a -> IO b) -> IO b
27
28   reallocArray,   -- :: Storable a => Ptr a -> Int -> IO (Ptr a)
29   reallocArray0,  -- :: Storable a => Ptr a -> Int -> IO (Ptr a)
30
31   -- ** Marshalling
32   --
33   peekArray,      -- :: Storable a =>         Int -> Ptr a -> IO [a]
34   peekArray0,     -- :: (Storable a, Eq a) => a   -> Ptr a -> IO [a]
35
36   pokeArray,      -- :: Storable a =>      Ptr a -> [a] -> IO ()
37   pokeArray0,     -- :: Storable a => a -> Ptr a -> [a] -> IO ()
38
39   -- ** Combined allocation and marshalling
40   --
41   newArray,       -- :: Storable a =>      [a] -> IO (Ptr a)
42   newArray0,      -- :: Storable a => a -> [a] -> IO (Ptr a)
43
44   withArray,      -- :: Storable a =>      [a] -> (Ptr a -> IO b) -> IO b
45   withArray0,     -- :: Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
46
47   -- ** Copying
48
49   -- | (argument order: destination, source)
50   copyArray,      -- :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
51   moveArray,      -- :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
52
53   -- ** Finding the length
54   --
55   lengthArray0,   -- :: (Storable a, Eq a) => a -> Ptr a -> IO Int
56
57   -- ** Indexing
58   --
59   advancePtr,     -- :: Storable a => Ptr a -> Int -> Ptr a
60 ) where
61
62 import Control.Monad
63
64 #ifdef __GLASGOW_HASKELL__
65 import Foreign.Ptr              (Ptr, plusPtr)
66 import GHC.Storable     (Storable(sizeOf,peekElemOff,pokeElemOff))
67 import Foreign.Marshal.Alloc (alloca, mallocBytes, allocaBytes, reallocBytes)
68 import Foreign.Marshal.Utils (copyBytes, moveBytes)
69 import GHC.IOBase
70 import GHC.Num
71 import GHC.List
72 import GHC.Err
73 import GHC.Base
74 #endif
75
76 -- allocation
77 -- ----------
78
79 -- |Allocate storage for the given number of elements of a storable type.
80 --
81 mallocArray :: Storable a => Int -> IO (Ptr a)
82 mallocArray  = doMalloc undefined
83   where
84     doMalloc            :: Storable a => a -> Int -> IO (Ptr a)
85     doMalloc dummy size  = mallocBytes (size * sizeOf dummy)
86
87 -- |Like 'mallocArray', but add an extra element to signal the end of the array
88 --
89 mallocArray0      :: Storable a => Int -> IO (Ptr a)
90 mallocArray0 size  = mallocArray (size + 1)
91
92 -- |Temporarily allocate space for the given number of elements.
93 --
94 -- * see 'Foreign.Marshal.Alloc.alloca' for the storage lifetime constraints
95 --
96 allocaArray :: Storable a => Int -> (Ptr a -> IO b) -> IO b
97 allocaArray  = doAlloca undefined
98   where
99     doAlloca            :: Storable a => a -> Int -> (Ptr a -> IO b) -> IO b
100     doAlloca dummy size  = allocaBytes (size * sizeOf dummy)
101
102 -- |Like 'allocaArray', but add an extra element to signal the end of the array
103 --
104 allocaArray0      :: Storable a => Int -> (Ptr a -> IO b) -> IO b
105 allocaArray0 size  = allocaArray (size + 1)
106
107 -- |Adjust the size of an array
108 --
109 reallocArray :: Storable a => Ptr a -> Int -> IO (Ptr a)
110 reallocArray  = doRealloc undefined
111   where
112     doRealloc                :: Storable a => a -> Ptr a -> Int -> IO (Ptr a)
113     doRealloc dummy ptr size  = reallocBytes ptr (size * sizeOf dummy)
114
115 -- |Adjust the size of an array while adding an element for the end marker
116 --
117 reallocArray0          :: Storable a => Ptr a -> Int -> IO (Ptr a)
118 reallocArray0 ptr size  = reallocArray ptr (size + 1)
119
120
121 -- marshalling
122 -- -----------
123
124 -- |Convert an array of given length into a Haskell list.  This version
125 -- traverses the array backwards using an accumulating parameter,
126 -- which uses constant stack space.  The previous version using mapM
127 -- needed linear stack space.
128 --
129 peekArray          :: Storable a => Int -> Ptr a -> IO [a]
130 peekArray size ptr | size <= 0 = return []
131                  | otherwise = f (size-1) []
132   where
133     f 0 acc = do e <- peekElemOff ptr 0; return (e:acc)
134     f n acc = do e <- peekElemOff ptr n; f (n-1) (e:acc)
135   
136 -- |Convert an array terminated by the given end marker into a Haskell list
137 --
138 peekArray0            :: (Storable a, Eq a) => a -> Ptr a -> IO [a]
139 peekArray0 marker ptr  = loop 0
140   where
141     loop i = do
142         val <- peekElemOff ptr i
143         if val == marker then return [] else do
144             rest <- loop (i+1)
145             return (val:rest)
146
147 -- |Write the list elements consecutive into memory
148 --
149 pokeArray          :: Storable a => Ptr a -> [a] -> IO ()
150 pokeArray ptr vals  = zipWithM_ (pokeElemOff ptr) [0..] vals
151
152 -- |Write the list elements consecutive into memory and terminate them with the
153 -- given marker element
154 --
155 pokeArray0                 :: Storable a => a -> Ptr a -> [a] -> IO ()
156 pokeArray0 marker ptr vals  = do
157   pokeArray ptr vals
158   pokeElemOff ptr (length vals) marker
159
160
161 -- combined allocation and marshalling
162 -- -----------------------------------
163
164 -- |Write a list of storable elements into a newly allocated, consecutive
165 -- sequence of storable values
166 --
167 newArray      :: Storable a => [a] -> IO (Ptr a)
168 newArray vals  = do
169   ptr <- mallocArray (length vals)
170   pokeArray ptr vals
171   return ptr
172
173 -- |Write a list of storable elements into a newly allocated, consecutive
174 -- sequence of storable values, where the end is fixed by the given end marker
175 --
176 newArray0             :: Storable a => a -> [a] -> IO (Ptr a)
177 newArray0 marker vals  = do
178   ptr <- mallocArray0 (length vals)
179   pokeArray0 marker ptr vals
180   return ptr
181
182 -- |Temporarily store a list of storable values in memory
183 --
184 withArray        :: Storable a => [a] -> (Ptr a -> IO b) -> IO b
185 withArray vals f  =
186   allocaArray len $ \ptr -> do
187       pokeArray ptr vals
188       res <- f ptr
189       return res
190   where
191     len = length vals
192
193 -- |Like 'withArray', but a terminator indicates where the array ends
194 --
195 withArray0               :: Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
196 withArray0 marker vals f  =
197   allocaArray0 len $ \ptr -> do
198       pokeArray0 marker ptr vals
199       res <- f ptr
200       return res
201   where
202     len = length vals
203
204
205 -- copying (argument order: destination, source)
206 -- -------
207
208 -- |Copy the given number of elements from the second array (source) into the
209 -- first array (destination); the copied areas may /not/ overlap
210 --
211 copyArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
212 copyArray  = doCopy undefined
213   where
214     doCopy                     :: Storable a => a -> Ptr a -> Ptr a -> Int -> IO ()
215     doCopy dummy dest src size  = copyBytes dest src (size * sizeOf dummy)
216
217 -- |Copy the given number of elements from the second array (source) into the
218 -- first array (destination); the copied areas /may/ overlap
219 --
220 moveArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
221 moveArray  = doMove undefined
222   where
223     doMove                     :: Storable a => a -> Ptr a -> Ptr a -> Int -> IO ()
224     doMove dummy dest src size  = moveBytes dest src (size * sizeOf dummy)
225
226
227 -- finding the length
228 -- ------------------
229
230 -- |Return the number of elements in an array, excluding the terminator
231 --
232 lengthArray0            :: (Storable a, Eq a) => a -> Ptr a -> IO Int
233 lengthArray0 marker ptr  = loop 0
234   where
235     loop i = do
236         val <- peekElemOff ptr i
237         if val == marker then return i else loop (i+1)
238
239
240 -- indexing
241 -- --------
242
243 -- |Advance a pointer into an array by the given number of elements
244 --
245 advancePtr :: Storable a => Ptr a -> Int -> Ptr a
246 advancePtr  = doAdvance undefined
247   where
248     doAdvance             :: Storable a => a -> Ptr a -> Int -> Ptr a
249     doAdvance dummy ptr i  = ptr `plusPtr` (i * sizeOf dummy)