[project @ 2002-08-03 19:32:16 by reid]
[ghc-base.git] / Foreign / Storable.lhs
1 \begin{code}
2 {-# OPTIONS -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Storable
6 -- Copyright   :  (c) The FFI task force, 2000-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  ffi@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- The 'Storable' class.
14 --
15 -----------------------------------------------------------------------------
16
17 #include "MachDeps.h"
18
19 module GHC.Storable
20         ( Storable(
21              sizeOf,         -- :: a -> Int
22              alignment,      -- :: a -> Int
23              peekElemOff,    -- :: Ptr a -> Int      -> IO a
24              pokeElemOff,    -- :: Ptr a -> Int -> a -> IO ()
25              peekByteOff,    -- :: Ptr b -> Int      -> IO a
26              pokeByteOff,    -- :: Ptr b -> Int -> a -> IO ()
27              peek,           -- :: Ptr a             -> IO a
28              poke)           -- :: Ptr a        -> a -> IO ()
29         ) where
30 \end{code}
31
32 \begin{code}
33 import Control.Monad            ( liftM )
34 import Foreign.C.Types
35 import Foreign.C.TypesISO
36
37 #ifdef __GLASGOW_HASKELL__
38 import GHC.Stable       ( StablePtr )
39 import GHC.Num
40 import GHC.Int
41 import GHC.Word
42 import GHC.Stable
43 import GHC.Ptr
44 import GHC.Float
45 import GHC.Err
46 import GHC.IOBase
47 import GHC.Base
48 #endif
49 \end{code}
50
51 Primitive marshaling
52
53 Minimal complete definition: sizeOf, alignment, and one definition
54 in each of the peek/poke families.
55
56 \begin{code}
57 {- |
58 The member functions of this class facilitate writing values of
59 primitive types to raw memory (which may have been allocated with the
60 above mentioned routines) and reading values from blocks of raw
61 memory.  The class, furthermore, includes support for computing the
62 storage requirements and alignment restrictions of storable types.
63
64 Memory addresses are represented as values of type @'Ptr' a@, for some
65 @a@ which is an instance of class 'Storable'.  The type argument to
66 'Ptr' helps provide some valuable type safety in FFI code (you can\'t
67 mix pointers of different types without an explicit cast), while
68 helping the Haskell type system figure out which marshalling method is
69 needed for a given pointer.
70
71 All marshalling between Haskell and a foreign language ultimately
72 boils down to translating Haskell data structures into the binary
73 representation of a corresponding data structure of the foreign
74 language and vice versa.  To code this marshalling in Haskell, it is
75 necessary to manipulate primtive data types stored in unstructured
76 memory blocks.  The class 'Storable' facilitates this manipulation on
77 all types for which it is instantiated, which are the standard basic
78 types of Haskell, the fixed size @Int@ types ('Int8', 'Int16',
79 'Int32', 'Int64'), the fixed size @Word@ types ('Word8', 'Word16',
80 'Word32', 'Word64'), 'StablePtr', all types from "CTypes" and
81 "CTypesISO", as well as 'Ptr'.
82
83 Minimal complete definition: 'sizeOf', 'alignment', one of 'peek',
84 'peekElemOff' and 'peekByteOff', and one of 'poke', 'pokeElemOff' and
85 'pokeByteOff'.
86 -}
87
88 class Storable a where
89
90    sizeOf      :: a -> Int
91    -- ^ Computes the storage requirements (in bytes) of the argument.
92    -- The value of the argument is not used.
93
94    alignment   :: a -> Int
95    -- ^ Computes the alignment constraint of the argument.  An
96    -- alignment constraint @x@ is fulfilled by any address divisible
97    -- by @x@.  The value of the argument is not used.
98
99    peekElemOff :: Ptr a -> Int      -> IO a
100    -- ^       Read a value from a memory area regarded as an array
101    --         of values of the same kind.  The first argument specifies
102    --         the start address of the array and the second the index into
103    --         the array (the first element of the array has index
104    --         @0@).  The following equality holds,
105    -- 
106    -- > peekElemOff addr idx = IOExts.fixIO $ \result ->
107    -- >   peek (addr \`plusPtr\` (idx * sizeOf result))
108    --
109    --         Note that this is only a specification, not
110    --         necessarily the concrete implementation of the
111    --         function.
112
113    pokeElemOff :: Ptr a -> Int -> a -> IO ()
114    -- ^       Write a value to a memory area regarded as an array of
115    --         values of the same kind.  The following equality holds:
116    -- 
117    -- > pokeElemOff addr idx x = 
118    -- >   poke (addr \`plusPtr\` (idx * sizeOf x)) x
119
120    peekByteOff :: Ptr b -> Int      -> IO a
121    -- ^       Read a value from a memory location given by a base
122    --         address and offset.  The following equality holds:
123    --
124    -- > peekByteOff addr off = peek (addr \`plusPtr\` off)
125
126    pokeByteOff :: Ptr b -> Int -> a -> IO ()
127    -- ^       Write a value to a memory location given by a base
128    --         address and offset.  The following equality holds:
129    --
130    -- > pokeByteOff addr off x = poke (addr \`plusPtr\` off) x
131   
132    peek        :: Ptr a      -> IO a
133    -- ^ Read a value from the given memory location.
134    --
135    --  Note that the peek and poke functions might require properly
136    --  aligned addresses to function correctly.  This is architecture
137    --  dependent; thus, portable code should ensure that when peeking or
138    --  poking values of some type @a@, the alignment
139    --  constraint for @a@, as given by the function
140    --  'alignment' is fulfilled.
141
142    poke        :: Ptr a -> a -> IO ()
143    -- ^ Write the given value to the given memory location.  Alignment
144    -- restrictions might apply; see 'peek'.
145  
146    -- circular default instances
147    peekElemOff = peekElemOff_ undefined
148       where peekElemOff_ :: a -> Ptr a -> Int -> IO a
149             peekElemOff_ undef ptr off = peekByteOff ptr (off * sizeOf undef)
150    pokeElemOff ptr off val = pokeByteOff ptr (off * sizeOf val) val
151
152    peekByteOff ptr off = peek (ptr `plusPtr` off)
153    pokeByteOff ptr off = poke (ptr `plusPtr` off)
154
155    peek ptr = peekElemOff ptr 0
156    poke ptr = pokeElemOff ptr 0
157 \end{code}
158
159 System-dependent, but rather obvious instances
160
161 \begin{code}
162 instance Storable Bool where
163    sizeOf _          = sizeOf (undefined::CInt)
164    alignment _       = alignment (undefined::CInt)
165    peekElemOff p i   = liftM (/= (0::CInt)) $ peekElemOff (castPtr p) i
166    pokeElemOff p i x = pokeElemOff (castPtr p) i (if x then 1 else 0::CInt)
167
168 #define STORABLE(T,size,align,read,write)       \
169 instance Storable (T) where {                   \
170     sizeOf    _ = size;                         \
171     alignment _ = align;                        \
172     peekElemOff = read;                         \
173     pokeElemOff = write }
174
175 STORABLE(Char,SIZEOF_INT32,ALIGNMENT_INT32,
176          readWideCharOffPtr,writeWideCharOffPtr)
177
178 STORABLE(Int,SIZEOF_HSINT,ALIGNMENT_HSINT,
179          readIntOffPtr,writeIntOffPtr)
180
181 #ifdef __GLASGOW_HASKELL__
182 STORABLE(Word,SIZEOF_HSWORD,ALIGNMENT_HSWORD,
183          readWordOffPtr,writeWordOffPtr)
184 #endif
185
186 STORABLE((Ptr a),SIZEOF_HSPTR,ALIGNMENT_HSPTR,
187          readPtrOffPtr,writePtrOffPtr)
188
189 STORABLE((FunPtr a),SIZEOF_HSFUNPTR,ALIGNMENT_HSFUNPTR,
190          readFunPtrOffPtr,writeFunPtrOffPtr)
191
192 STORABLE((StablePtr a),SIZEOF_HSSTABLEPTR,ALIGNMENT_HSSTABLEPTR,
193          readStablePtrOffPtr,writeStablePtrOffPtr)
194
195 STORABLE(Float,SIZEOF_HSFLOAT,ALIGNMENT_HSFLOAT,
196          readFloatOffPtr,writeFloatOffPtr)
197
198 STORABLE(Double,SIZEOF_HSDOUBLE,ALIGNMENT_HSDOUBLE,
199          readDoubleOffPtr,writeDoubleOffPtr)
200
201 STORABLE(Word8,SIZEOF_WORD8,ALIGNMENT_WORD8,
202          readWord8OffPtr,writeWord8OffPtr)
203
204 STORABLE(Word16,SIZEOF_WORD16,ALIGNMENT_WORD16,
205          readWord16OffPtr,writeWord16OffPtr)
206
207 STORABLE(Word32,SIZEOF_WORD32,ALIGNMENT_WORD32,
208          readWord32OffPtr,writeWord32OffPtr)
209
210 STORABLE(Word64,SIZEOF_WORD64,ALIGNMENT_WORD64,
211          readWord64OffPtr,writeWord64OffPtr)
212
213 STORABLE(Int8,SIZEOF_INT8,ALIGNMENT_INT8,
214          readInt8OffPtr,writeInt8OffPtr)
215
216 STORABLE(Int16,SIZEOF_INT16,ALIGNMENT_INT16,
217          readInt16OffPtr,writeInt16OffPtr)
218
219 STORABLE(Int32,SIZEOF_INT32,ALIGNMENT_INT32,
220          readInt32OffPtr,writeInt32OffPtr)
221
222 STORABLE(Int64,SIZEOF_INT64,ALIGNMENT_INT64,
223          readInt64OffPtr,writeInt64OffPtr)
224
225 #define NSTORABLE(T) \
226 instance Storable T where { \
227    sizeOf    (T x)       = sizeOf x ; \
228    alignment (T x)       = alignment x ; \
229    peekElemOff a i       = liftM T (peekElemOff (castPtr a) i) ; \
230    pokeElemOff a i (T x) = pokeElemOff (castPtr a) i x }
231
232 NSTORABLE(CChar)
233 NSTORABLE(CSChar)
234 NSTORABLE(CUChar)
235 NSTORABLE(CShort)
236 NSTORABLE(CUShort)
237 NSTORABLE(CInt)
238 NSTORABLE(CUInt)
239 NSTORABLE(CLong)
240 NSTORABLE(CULong)
241 NSTORABLE(CLLong)
242 NSTORABLE(CULLong)
243 NSTORABLE(CFloat)
244 NSTORABLE(CDouble)
245 NSTORABLE(CLDouble)
246 NSTORABLE(CPtrdiff)
247 NSTORABLE(CSize)
248 NSTORABLE(CWchar)
249 NSTORABLE(CSigAtomic)
250 NSTORABLE(CClock)
251 NSTORABLE(CTime)
252 \end{code}
253
254 Helper functions
255
256 \begin{code}
257 #ifdef __GLASGOW_HASKELL__
258
259 readWideCharOffPtr  :: Ptr Char          -> Int -> IO Char
260 readIntOffPtr       :: Ptr Int           -> Int -> IO Int
261 readWordOffPtr      :: Ptr Word          -> Int -> IO Word
262 readPtrOffPtr       :: Ptr (Ptr a)       -> Int -> IO (Ptr a)
263 readFunPtrOffPtr    :: Ptr (FunPtr a)    -> Int -> IO (FunPtr a)
264 readFloatOffPtr     :: Ptr Float         -> Int -> IO Float
265 readDoubleOffPtr    :: Ptr Double        -> Int -> IO Double
266 readStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> IO (StablePtr a)
267 readInt8OffPtr      :: Ptr Int8          -> Int -> IO Int8
268 readInt16OffPtr     :: Ptr Int16         -> Int -> IO Int16
269 readInt32OffPtr     :: Ptr Int32         -> Int -> IO Int32
270 readInt64OffPtr     :: Ptr Int64         -> Int -> IO Int64
271 readWord8OffPtr     :: Ptr Word8         -> Int -> IO Word8
272 readWord16OffPtr    :: Ptr Word16        -> Int -> IO Word16
273 readWord32OffPtr    :: Ptr Word32        -> Int -> IO Word32
274 readWord64OffPtr    :: Ptr Word64        -> Int -> IO Word64
275
276 readWideCharOffPtr (Ptr a) (I# i)
277   = IO $ \s -> case readWideCharOffAddr# a i s  of (# s2, x #) -> (# s2, C# x #)
278 readIntOffPtr (Ptr a) (I# i)
279   = IO $ \s -> case readIntOffAddr# a i s       of (# s2, x #) -> (# s2, I# x #)
280 readWordOffPtr (Ptr a) (I# i)
281   = IO $ \s -> case readWordOffAddr# a i s      of (# s2, x #) -> (# s2, W# x #)
282 readPtrOffPtr (Ptr a) (I# i)
283   = IO $ \s -> case readAddrOffAddr# a i s      of (# s2, x #) -> (# s2, Ptr x #)
284 readFunPtrOffPtr (Ptr a) (I# i)
285   = IO $ \s -> case readAddrOffAddr# a i s      of (# s2, x #) -> (# s2, FunPtr x #)
286 readFloatOffPtr (Ptr a) (I# i)
287   = IO $ \s -> case readFloatOffAddr# a i s     of (# s2, x #) -> (# s2, F# x #)
288 readDoubleOffPtr (Ptr a) (I# i)
289   = IO $ \s -> case readDoubleOffAddr# a i s    of (# s2, x #) -> (# s2, D# x #)
290 readStablePtrOffPtr (Ptr a) (I# i)
291   = IO $ \s -> case readStablePtrOffAddr# a i s of (# s2, x #) -> (# s2, StablePtr x #)
292 readInt8OffPtr (Ptr a) (I# i)
293   = IO $ \s -> case readInt8OffAddr# a i s      of (# s2, x #) -> (# s2, I8# x #)
294 readWord8OffPtr (Ptr a) (I# i)
295   = IO $ \s -> case readWord8OffAddr# a i s     of (# s2, x #) -> (# s2, W8# x #)
296 readInt16OffPtr (Ptr a) (I# i)
297   = IO $ \s -> case readInt16OffAddr# a i s     of (# s2, x #) -> (# s2, I16# x #)
298 readWord16OffPtr (Ptr a) (I# i)
299   = IO $ \s -> case readWord16OffAddr# a i s    of (# s2, x #) -> (# s2, W16# x #)
300 readInt32OffPtr (Ptr a) (I# i)
301   = IO $ \s -> case readInt32OffAddr# a i s     of (# s2, x #) -> (# s2, I32# x #)
302 readWord32OffPtr (Ptr a) (I# i)
303   = IO $ \s -> case readWord32OffAddr# a i s    of (# s2, x #) -> (# s2, W32# x #)
304 readInt64OffPtr (Ptr a) (I# i)
305   = IO $ \s -> case readInt64OffAddr# a i s     of (# s2, x #) -> (# s2, I64# x #)
306 readWord64OffPtr (Ptr a) (I# i)
307   = IO $ \s -> case readWord64OffAddr# a i s    of (# s2, x #) -> (# s2, W64# x #)
308
309 writeWideCharOffPtr  :: Ptr Char          -> Int -> Char        -> IO ()
310 writeIntOffPtr       :: Ptr Int           -> Int -> Int         -> IO ()
311 writeWordOffPtr      :: Ptr Word          -> Int -> Word        -> IO ()
312 writePtrOffPtr       :: Ptr (Ptr a)       -> Int -> Ptr a       -> IO ()
313 writeFunPtrOffPtr    :: Ptr (FunPtr a)    -> Int -> FunPtr a    -> IO ()
314 writeFloatOffPtr     :: Ptr Float         -> Int -> Float       -> IO ()
315 writeDoubleOffPtr    :: Ptr Double        -> Int -> Double      -> IO ()
316 writeStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO ()
317 writeInt8OffPtr      :: Ptr Int8          -> Int -> Int8        -> IO ()
318 writeInt16OffPtr     :: Ptr Int16         -> Int -> Int16       -> IO ()
319 writeInt32OffPtr     :: Ptr Int32         -> Int -> Int32       -> IO ()
320 writeInt64OffPtr     :: Ptr Int64         -> Int -> Int64       -> IO ()
321 writeWord8OffPtr     :: Ptr Word8         -> Int -> Word8       -> IO ()
322 writeWord16OffPtr    :: Ptr Word16        -> Int -> Word16      -> IO ()
323 writeWord32OffPtr    :: Ptr Word32        -> Int -> Word32      -> IO ()
324 writeWord64OffPtr    :: Ptr Word64        -> Int -> Word64      -> IO ()
325
326 writeWideCharOffPtr (Ptr a) (I# i) (C# x)
327   = IO $ \s -> case writeWideCharOffAddr# a i x s  of s2 -> (# s2, () #)
328 writeIntOffPtr (Ptr a) (I# i) (I# x)
329   = IO $ \s -> case writeIntOffAddr# a i x s       of s2 -> (# s2, () #)
330 writeWordOffPtr (Ptr a) (I# i) (W# x)
331   = IO $ \s -> case writeWordOffAddr# a i x s      of s2 -> (# s2, () #)
332 writePtrOffPtr (Ptr a) (I# i) (Ptr x)
333   = IO $ \s -> case writeAddrOffAddr# a i x s      of s2 -> (# s2, () #)
334 writeFunPtrOffPtr (Ptr a) (I# i) (FunPtr x)
335   = IO $ \s -> case writeAddrOffAddr# a i x s      of s2 -> (# s2, () #)
336 writeFloatOffPtr (Ptr a) (I# i) (F# x)
337   = IO $ \s -> case writeFloatOffAddr# a i x s     of s2 -> (# s2, () #)
338 writeDoubleOffPtr (Ptr a) (I# i) (D# x)
339   = IO $ \s -> case writeDoubleOffAddr# a i x s    of s2 -> (# s2, () #)
340 writeStablePtrOffPtr (Ptr a) (I# i) (StablePtr x)
341   = IO $ \s -> case writeStablePtrOffAddr# a i x s of s2 -> (# s2 , () #)
342 writeInt8OffPtr (Ptr a) (I# i) (I8# x)
343   = IO $ \s -> case writeInt8OffAddr# a i x s      of s2 -> (# s2, () #)
344 writeWord8OffPtr (Ptr a) (I# i) (W8# x)
345   = IO $ \s -> case writeWord8OffAddr# a i x s     of s2 -> (# s2, () #)
346 writeInt16OffPtr (Ptr a) (I# i) (I16# x)
347   = IO $ \s -> case writeInt16OffAddr# a i x s     of s2 -> (# s2, () #)
348 writeWord16OffPtr (Ptr a) (I# i) (W16# x)
349   = IO $ \s -> case writeWord16OffAddr# a i x s    of s2 -> (# s2, () #)
350 writeInt32OffPtr (Ptr a) (I# i) (I32# x)
351   = IO $ \s -> case writeInt32OffAddr# a i x s     of s2 -> (# s2, () #)
352 writeWord32OffPtr (Ptr a) (I# i) (W32# x)
353   = IO $ \s -> case writeWord32OffAddr# a i x s    of s2 -> (# s2, () #)
354 writeInt64OffPtr (Ptr a) (I# i) (I64# x)
355   = IO $ \s -> case writeInt64OffAddr# a i x s     of s2 -> (# s2, () #)
356 writeWord64OffPtr (Ptr a) (I# i) (W64# x)
357   = IO $ \s -> case writeWord64OffAddr# a i x s    of s2 -> (# s2, () #)
358
359 #elif defined(__HUGS__)
360 /* 
361  * You might be surprised to find Hugs code in GHC.Storable - no more 
362  * surprised though than I was to find so much machine-independent code
363  * hiding in the GHC directory. - ADR
364  */
365
366 foreign import ccall unsafe "Storable_aux.h" readIntOffPtr       :: Ptr Int           -> Int -> IO Int
367 foreign import ccall unsafe "Storable_aux.h" readCharOffPtr      :: Ptr Char          -> Int -> IO Char
368 -- foreign import ccall unsafe "Storable_aux.h" readWideCharOffPtr  :: Ptr Char          -> Int -> IO Char
369 -- foreign import ccall unsafe "Storable_aux.h" readWordOffPtr      :: Ptr Word          -> Int -> IO Word
370 foreign import ccall unsafe "Storable_aux.h" readPtrOffPtr       :: Ptr (Ptr a)       -> Int -> IO (Ptr a)
371 foreign import ccall unsafe "Storable_aux.h" readFunPtrOffPtr    :: Ptr (FunPtr a)    -> Int -> IO (FunPtr a)
372 foreign import ccall unsafe "Storable_aux.h" readFloatOffPtr     :: Ptr Float         -> Int -> IO Float
373 foreign import ccall unsafe "Storable_aux.h" readDoubleOffPtr    :: Ptr Double        -> Int -> IO Double
374 foreign import ccall unsafe "Storable_aux.h" readStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> IO (StablePtr a)
375 foreign import ccall unsafe "Storable_aux.h" readInt8OffPtr      :: Ptr Int8          -> Int -> IO Int8
376 foreign import ccall unsafe "Storable_aux.h" readInt16OffPtr     :: Ptr Int16         -> Int -> IO Int16
377 foreign import ccall unsafe "Storable_aux.h" readInt32OffPtr     :: Ptr Int32         -> Int -> IO Int32
378 foreign import ccall unsafe "Storable_aux.h" readInt64OffPtr     :: Ptr Int64         -> Int -> IO Int64
379 foreign import ccall unsafe "Storable_aux.h" readWord8OffPtr     :: Ptr Word8         -> Int -> IO Word8
380 foreign import ccall unsafe "Storable_aux.h" readWord16OffPtr    :: Ptr Word16        -> Int -> IO Word16
381 foreign import ccall unsafe "Storable_aux.h" readWord32OffPtr    :: Ptr Word32        -> Int -> IO Word32
382 foreign import ccall unsafe "Storable_aux.h" readWord64OffPtr    :: Ptr Word64        -> Int -> IO Word64
383
384 foreign import ccall unsafe "Storable_aux.h" writeIntOffPtr       :: Ptr Int           -> Int -> Int         -> IO ()
385 foreign import ccall unsafe "Storable_aux.h" writeCharOffPtr      :: Ptr Char          -> Int -> Char        -> IO ()
386 foreign import ccall unsafe "Storable_aux.h" writeWideCharOffPtr  :: Ptr Char          -> Int -> Char        -> IO ()
387 foreign import ccall unsafe "Storable_aux.h" writeWordOffPtr      :: Ptr Word          -> Int -> Word        -> IO ()
388 foreign import ccall unsafe "Storable_aux.h" writePtrOffPtr       :: Ptr (Ptr a)       -> Int -> Ptr a       -> IO ()
389 foreign import ccall unsafe "Storable_aux.h" writeFunPtrOffPtr    :: Ptr (FunPtr a)    -> Int -> FunPtr a    -> IO ()
390 foreign import ccall unsafe "Storable_aux.h" writeFloatOffPtr     :: Ptr Float         -> Int -> Float       -> IO ()
391 foreign import ccall unsafe "Storable_aux.h" writeDoubleOffPtr    :: Ptr Double        -> Int -> Double      -> IO ()
392 foreign import ccall unsafe "Storable_aux.h" writeStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO ()
393 foreign import ccall unsafe "Storable_aux.h" writeInt8OffPtr      :: Ptr Int8          -> Int -> Int8        -> IO ()
394 foreign import ccall unsafe "Storable_aux.h" writeInt16OffPtr     :: Ptr Int16         -> Int -> Int16       -> IO ()
395 foreign import ccall unsafe "Storable_aux.h" writeInt32OffPtr     :: Ptr Int32         -> Int -> Int32       -> IO ()
396 foreign import ccall unsafe "Storable_aux.h" writeInt64OffPtr     :: Ptr Int64         -> Int -> Int64       -> IO ()
397 foreign import ccall unsafe "Storable_aux.h" writeWord8OffPtr     :: Ptr Word8         -> Int -> Word8       -> IO ()
398 foreign import ccall unsafe "Storable_aux.h" writeWord16OffPtr    :: Ptr Word16        -> Int -> Word16      -> IO ()
399 foreign import ccall unsafe "Storable_aux.h" writeWord32OffPtr    :: Ptr Word32        -> Int -> Word32      -> IO ()
400 foreign import ccall unsafe "Storable_aux.h" writeWord64OffPtr    :: Ptr Word64        -> Int -> Word64      -> IO ()
401
402 #endif /* __HUGS__ */
403 \end{code}