[project @ 2002-08-02 12:26:36 by simonmar]
[ghc-base.git] / GHC / 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 STORABLE(Word,SIZEOF_HSWORD,ALIGNMENT_HSWORD,
182          readWordOffPtr,writeWordOffPtr)
183
184 STORABLE((Ptr a),SIZEOF_HSPTR,ALIGNMENT_HSPTR,
185          readPtrOffPtr,writePtrOffPtr)
186
187 STORABLE((FunPtr a),SIZEOF_HSFUNPTR,ALIGNMENT_HSFUNPTR,
188          readFunPtrOffPtr,writeFunPtrOffPtr)
189
190 STORABLE((StablePtr a),SIZEOF_HSSTABLEPTR,ALIGNMENT_HSSTABLEPTR,
191          readStablePtrOffPtr,writeStablePtrOffPtr)
192
193 STORABLE(Float,SIZEOF_HSFLOAT,ALIGNMENT_HSFLOAT,
194          readFloatOffPtr,writeFloatOffPtr)
195
196 STORABLE(Double,SIZEOF_HSDOUBLE,ALIGNMENT_HSDOUBLE,
197          readDoubleOffPtr,writeDoubleOffPtr)
198
199 STORABLE(Word8,SIZEOF_WORD8,ALIGNMENT_WORD8,
200          readWord8OffPtr,writeWord8OffPtr)
201
202 STORABLE(Word16,SIZEOF_WORD16,ALIGNMENT_WORD16,
203          readWord16OffPtr,writeWord16OffPtr)
204
205 STORABLE(Word32,SIZEOF_WORD32,ALIGNMENT_WORD32,
206          readWord32OffPtr,writeWord32OffPtr)
207
208 STORABLE(Word64,SIZEOF_WORD64,ALIGNMENT_WORD64,
209          readWord64OffPtr,writeWord64OffPtr)
210
211 STORABLE(Int8,SIZEOF_INT8,ALIGNMENT_INT8,
212          readInt8OffPtr,writeInt8OffPtr)
213
214 STORABLE(Int16,SIZEOF_INT16,ALIGNMENT_INT16,
215          readInt16OffPtr,writeInt16OffPtr)
216
217 STORABLE(Int32,SIZEOF_INT32,ALIGNMENT_INT32,
218          readInt32OffPtr,writeInt32OffPtr)
219
220 STORABLE(Int64,SIZEOF_INT64,ALIGNMENT_INT64,
221          readInt64OffPtr,writeInt64OffPtr)
222
223 #define NSTORABLE(T) \
224 instance Storable T where { \
225    sizeOf    (T x)       = sizeOf x ; \
226    alignment (T x)       = alignment x ; \
227    peekElemOff a i       = liftM T (peekElemOff (castPtr a) i) ; \
228    pokeElemOff a i (T x) = pokeElemOff (castPtr a) i x }
229
230 NSTORABLE(CChar)
231 NSTORABLE(CSChar)
232 NSTORABLE(CUChar)
233 NSTORABLE(CShort)
234 NSTORABLE(CUShort)
235 NSTORABLE(CInt)
236 NSTORABLE(CUInt)
237 NSTORABLE(CLong)
238 NSTORABLE(CULong)
239 NSTORABLE(CLLong)
240 NSTORABLE(CULLong)
241 NSTORABLE(CFloat)
242 NSTORABLE(CDouble)
243 NSTORABLE(CLDouble)
244 NSTORABLE(CPtrdiff)
245 NSTORABLE(CSize)
246 NSTORABLE(CWchar)
247 NSTORABLE(CSigAtomic)
248 NSTORABLE(CClock)
249 NSTORABLE(CTime)
250 \end{code}
251
252 Helper functions
253
254 \begin{code}
255 #ifdef __GLASGOW_HASKELL__
256
257 readWideCharOffPtr  :: Ptr Char          -> Int -> IO Char
258 readIntOffPtr       :: Ptr Int           -> Int -> IO Int
259 readWordOffPtr      :: Ptr Word          -> Int -> IO Word
260 readPtrOffPtr       :: Ptr (Ptr a)       -> Int -> IO (Ptr a)
261 readFunPtrOffPtr    :: Ptr (FunPtr a)    -> Int -> IO (FunPtr a)
262 readFloatOffPtr     :: Ptr Float         -> Int -> IO Float
263 readDoubleOffPtr    :: Ptr Double        -> Int -> IO Double
264 readStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> IO (StablePtr a)
265 readInt8OffPtr      :: Ptr Int8          -> Int -> IO Int8
266 readInt16OffPtr     :: Ptr Int16         -> Int -> IO Int16
267 readInt32OffPtr     :: Ptr Int32         -> Int -> IO Int32
268 readInt64OffPtr     :: Ptr Int64         -> Int -> IO Int64
269 readWord8OffPtr     :: Ptr Word8         -> Int -> IO Word8
270 readWord16OffPtr    :: Ptr Word16        -> Int -> IO Word16
271 readWord32OffPtr    :: Ptr Word32        -> Int -> IO Word32
272 readWord64OffPtr    :: Ptr Word64        -> Int -> IO Word64
273
274 readWideCharOffPtr (Ptr a) (I# i)
275   = IO $ \s -> case readWideCharOffAddr# a i s  of (# s2, x #) -> (# s2, C# x #)
276 readIntOffPtr (Ptr a) (I# i)
277   = IO $ \s -> case readIntOffAddr# a i s       of (# s2, x #) -> (# s2, I# x #)
278 readWordOffPtr (Ptr a) (I# i)
279   = IO $ \s -> case readWordOffAddr# a i s      of (# s2, x #) -> (# s2, W# x #)
280 readPtrOffPtr (Ptr a) (I# i)
281   = IO $ \s -> case readAddrOffAddr# a i s      of (# s2, x #) -> (# s2, Ptr x #)
282 readFunPtrOffPtr (Ptr a) (I# i)
283   = IO $ \s -> case readAddrOffAddr# a i s      of (# s2, x #) -> (# s2, FunPtr x #)
284 readFloatOffPtr (Ptr a) (I# i)
285   = IO $ \s -> case readFloatOffAddr# a i s     of (# s2, x #) -> (# s2, F# x #)
286 readDoubleOffPtr (Ptr a) (I# i)
287   = IO $ \s -> case readDoubleOffAddr# a i s    of (# s2, x #) -> (# s2, D# x #)
288 readStablePtrOffPtr (Ptr a) (I# i)
289   = IO $ \s -> case readStablePtrOffAddr# a i s of (# s2, x #) -> (# s2, StablePtr x #)
290 readInt8OffPtr (Ptr a) (I# i)
291   = IO $ \s -> case readInt8OffAddr# a i s      of (# s2, x #) -> (# s2, I8# x #)
292 readWord8OffPtr (Ptr a) (I# i)
293   = IO $ \s -> case readWord8OffAddr# a i s     of (# s2, x #) -> (# s2, W8# x #)
294 readInt16OffPtr (Ptr a) (I# i)
295   = IO $ \s -> case readInt16OffAddr# a i s     of (# s2, x #) -> (# s2, I16# x #)
296 readWord16OffPtr (Ptr a) (I# i)
297   = IO $ \s -> case readWord16OffAddr# a i s    of (# s2, x #) -> (# s2, W16# x #)
298 readInt32OffPtr (Ptr a) (I# i)
299   = IO $ \s -> case readInt32OffAddr# a i s     of (# s2, x #) -> (# s2, I32# x #)
300 readWord32OffPtr (Ptr a) (I# i)
301   = IO $ \s -> case readWord32OffAddr# a i s    of (# s2, x #) -> (# s2, W32# x #)
302 readInt64OffPtr (Ptr a) (I# i)
303   = IO $ \s -> case readInt64OffAddr# a i s     of (# s2, x #) -> (# s2, I64# x #)
304 readWord64OffPtr (Ptr a) (I# i)
305   = IO $ \s -> case readWord64OffAddr# a i s    of (# s2, x #) -> (# s2, W64# x #)
306
307 writeWideCharOffPtr  :: Ptr Char          -> Int -> Char        -> IO ()
308 writeIntOffPtr       :: Ptr Int           -> Int -> Int         -> IO ()
309 writeWordOffPtr      :: Ptr Word          -> Int -> Word        -> IO ()
310 writePtrOffPtr       :: Ptr (Ptr a)       -> Int -> Ptr a       -> IO ()
311 writeFunPtrOffPtr    :: Ptr (FunPtr a)    -> Int -> FunPtr a    -> IO ()
312 writeFloatOffPtr     :: Ptr Float         -> Int -> Float       -> IO ()
313 writeDoubleOffPtr    :: Ptr Double        -> Int -> Double      -> IO ()
314 writeStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO ()
315 writeInt8OffPtr      :: Ptr Int8          -> Int -> Int8        -> IO ()
316 writeInt16OffPtr     :: Ptr Int16         -> Int -> Int16       -> IO ()
317 writeInt32OffPtr     :: Ptr Int32         -> Int -> Int32       -> IO ()
318 writeInt64OffPtr     :: Ptr Int64         -> Int -> Int64       -> IO ()
319 writeWord8OffPtr     :: Ptr Word8         -> Int -> Word8       -> IO ()
320 writeWord16OffPtr    :: Ptr Word16        -> Int -> Word16      -> IO ()
321 writeWord32OffPtr    :: Ptr Word32        -> Int -> Word32      -> IO ()
322 writeWord64OffPtr    :: Ptr Word64        -> Int -> Word64      -> IO ()
323
324 writeWideCharOffPtr (Ptr a) (I# i) (C# x)
325   = IO $ \s -> case writeWideCharOffAddr# a i x s  of s2 -> (# s2, () #)
326 writeIntOffPtr (Ptr a) (I# i) (I# x)
327   = IO $ \s -> case writeIntOffAddr# a i x s       of s2 -> (# s2, () #)
328 writeWordOffPtr (Ptr a) (I# i) (W# x)
329   = IO $ \s -> case writeWordOffAddr# a i x s      of s2 -> (# s2, () #)
330 writePtrOffPtr (Ptr a) (I# i) (Ptr x)
331   = IO $ \s -> case writeAddrOffAddr# a i x s      of s2 -> (# s2, () #)
332 writeFunPtrOffPtr (Ptr a) (I# i) (FunPtr x)
333   = IO $ \s -> case writeAddrOffAddr# a i x s      of s2 -> (# s2, () #)
334 writeFloatOffPtr (Ptr a) (I# i) (F# x)
335   = IO $ \s -> case writeFloatOffAddr# a i x s     of s2 -> (# s2, () #)
336 writeDoubleOffPtr (Ptr a) (I# i) (D# x)
337   = IO $ \s -> case writeDoubleOffAddr# a i x s    of s2 -> (# s2, () #)
338 writeStablePtrOffPtr (Ptr a) (I# i) (StablePtr x)
339   = IO $ \s -> case writeStablePtrOffAddr# a i x s of s2 -> (# s2 , () #)
340 writeInt8OffPtr (Ptr a) (I# i) (I8# x)
341   = IO $ \s -> case writeInt8OffAddr# a i x s      of s2 -> (# s2, () #)
342 writeWord8OffPtr (Ptr a) (I# i) (W8# x)
343   = IO $ \s -> case writeWord8OffAddr# a i x s     of s2 -> (# s2, () #)
344 writeInt16OffPtr (Ptr a) (I# i) (I16# x)
345   = IO $ \s -> case writeInt16OffAddr# a i x s     of s2 -> (# s2, () #)
346 writeWord16OffPtr (Ptr a) (I# i) (W16# x)
347   = IO $ \s -> case writeWord16OffAddr# a i x s    of s2 -> (# s2, () #)
348 writeInt32OffPtr (Ptr a) (I# i) (I32# x)
349   = IO $ \s -> case writeInt32OffAddr# a i x s     of s2 -> (# s2, () #)
350 writeWord32OffPtr (Ptr a) (I# i) (W32# x)
351   = IO $ \s -> case writeWord32OffAddr# a i x s    of s2 -> (# s2, () #)
352 writeInt64OffPtr (Ptr a) (I# i) (I64# x)
353   = IO $ \s -> case writeInt64OffAddr# a i x s     of s2 -> (# s2, () #)
354 writeWord64OffPtr (Ptr a) (I# i) (W64# x)
355   = IO $ \s -> case writeWord64OffAddr# a i x s    of s2 -> (# s2, () #)
356
357 #endif /* __GLASGOW_HASKELL__ */
358 \end{code}