[project @ 1998-08-14 13:00:57 by sof]
[ghc-hetmet.git] / ghc / lib / exts / Word.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1997
3 %
4 \section[Word]{Module @Word@}
5
6 GHC implementation of the standard Hugs/GHC @Word@
7 interface, types and operations over unsigned, sized
8 quantities.
9
10 \begin{code}
11 #include "MachDeps.h"
12
13 module Word
14         ( Word8          -- all abstract.
15         , Word16         -- instances: Eq, Ord
16         , Word32         --  Num, Bounded, Real,
17         , Word64         --  Integral, Ix, Enum,
18                          --  Read, Show, Bits,
19                          --  CCallable, CReturnable
20                          --  (last two 
21
22         , word8ToWord32   -- :: Word8  -> Word32
23         , word32ToWord8   -- :: Word32 -> Word8
24         , word16ToWord32  -- :: Word16 -> Word32
25         , word32ToWord16  -- :: Word32 -> Word16
26
27         , word8ToInt      -- :: Word8  -> Int
28         , intToWord8      -- :: Int    -> Word8
29         , word16ToInt     -- :: Word16 -> Int
30         , intToWord16     -- :: Int    -> Word16
31         , word32ToInt     -- :: Word32 -> Int
32         , intToWord32     -- :: Int    -> Word32
33
34         , word32ToWord64  -- :: Word32 -> Word64
35         , word64ToWord32  -- :: Word64 -> Word32
36         
37         , word64ToInteger -- :: Word64  -> Integer
38         , integerToWord64 -- :: Integer -> Word64
39
40         -- NB! GHC SPECIFIC:
41         , wordToWord8     -- :: Word   -> Word8
42         , word8ToWord     -- :: Word8  -> Word
43         , wordToWord16    -- :: Word   -> Word16
44         , word16ToWord    -- :: Word16 -> Word
45         , wordToWord32    -- :: Word   -> Word32
46         , word32ToWord    -- :: Word32 -> Word
47         , wordToWord64    -- :: Word   -> Word64
48         , word64ToWord    -- :: Word64 -> Word
49
50         -- The "official" place to get these from is Addr.
51         , indexWord8OffAddr
52         , indexWord16OffAddr
53         , indexWord32OffAddr
54         , indexWord64OffAddr
55         
56         , readWord8OffAddr
57         , readWord16OffAddr
58         , readWord32OffAddr
59         , readWord64OffAddr
60         
61         , writeWord8OffAddr
62         , writeWord16OffAddr
63         , writeWord32OffAddr
64         , writeWord64OffAddr
65         
66         , sizeofWord8
67         , sizeofWord16
68         , sizeofWord32
69         , sizeofWord64
70
71         -- The "official" place to get these from is Foreign
72         , indexWord8OffForeignObj
73         , indexWord16OffForeignObj
74         , indexWord32OffForeignObj
75         , indexWord64OffForeignObj
76         
77         , readWord8OffForeignObj
78         , readWord16OffForeignObj
79         , readWord32OffForeignObj
80         , readWord64OffForeignObj
81         
82         , writeWord8OffForeignObj
83         , writeWord16OffForeignObj
84         , writeWord32OffForeignObj
85         , writeWord64OffForeignObj
86         
87         -- non-standard, GHC specific
88         , wordToInt
89
90         ) where
91
92 import GlaExts
93 import Ix
94 import Bits
95 import CCall
96 import Numeric (readDec, showInt)
97 import PrelForeign
98 import PrelIOBase
99
100 -----------------------------------------------------------------------------
101 -- The "official" coercion functions
102 -----------------------------------------------------------------------------
103
104 word8ToWord32  :: Word8  -> Word32
105 word32ToWord8  :: Word32 -> Word8
106 word16ToWord32 :: Word16 -> Word32
107 word32ToWord16 :: Word32 -> Word16
108
109 word8ToInt   :: Word8  -> Int
110 intToWord8   :: Int    -> Word8
111 word16ToInt  :: Word16 -> Int
112 intToWord16  :: Int    -> Word16
113
114 word8ToInt  = word32ToInt    . word8ToWord32
115 intToWord8  = word32ToWord8  . intToWord32
116 word16ToInt = word32ToInt    . word16ToWord32
117 intToWord16 = word32ToWord16 . intToWord32
118
119 intToWord32 (I# x)   = W32# ((int2Word# x) `and#` (case (maxBound::Word32) of W32# x# -> x#))
120 --intToWord32 (I# x)   = W32# (int2Word# x)
121 word32ToInt (W32# x) = I#   (word2Int# x)
122
123 wordToInt :: Word -> Int
124 wordToInt (W# w#) = I# (word2Int# w#)
125
126 \end{code}
127
128 \subsection[Word8]{The @Word8@ interface}
129
130 The byte type @Word8@ is represented in the Haskell
131 heap by boxing up a 32-bit quantity, @Word#@. An invariant
132 for this representation is that the higher 24 bits are
133 *always* zeroed out. A consequence of this is that
134 operations that could possibly overflow have to mask
135 out the top three bytes before building the resulting @Word8@.
136
137 \begin{code}
138 data Word8  = W8# Word#
139
140 instance CCallable Word8
141 instance CReturnable Word8
142
143 word8ToWord32 (W8#  x) = W32# x
144 word32ToWord8 (W32# x) = W8# (wordToWord8# x)
145
146 -- mask out upper three bytes.
147 intToWord8# :: Int# -> Word#
148 intToWord8# i# = (int2Word# i#) `and#` (int2Word# 0xff#)
149
150 wordToWord8# :: Word# -> Word#
151 wordToWord8# w# = w# `and#` (int2Word# 0xff#)
152
153 instance Eq  Word8     where 
154   (W8# x) == (W8# y) = x `eqWord#` y
155   (W8# x) /= (W8# y) = x `neWord#` y
156
157 instance Ord Word8     where 
158   compare (W8# x#) (W8# y#) = compareWord# x# y#
159   (<)  (W8# x) (W8# y)      = x `ltWord#` y
160   (<=) (W8# x) (W8# y)      = x `leWord#` y
161   (>=) (W8# x) (W8# y)      = x `geWord#` y
162   (>)  (W8# x) (W8# y)      = x `gtWord#` y
163   max x@(W8# x#) y@(W8# y#) = 
164      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
165   min x@(W8# x#) y@(W8# y#) =
166      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
167
168 -- Helper function, used by Ord Word* instances.
169 compareWord# :: Word# -> Word# -> Ordering
170 compareWord# x# y# 
171  | x# `ltWord#` y# = LT
172  | x# `eqWord#` y# = EQ
173  | otherwise       = GT
174
175 instance Num Word8 where
176   (W8# x) + (W8# y) = 
177       W8# (intToWord8# (word2Int# x +# word2Int# y))
178   (W8# x) - (W8# y) = 
179       W8# (intToWord8# (word2Int# x -# word2Int# y))
180   (W8# x) * (W8# y) = 
181       W8# (intToWord8# (word2Int# x *# word2Int# y))
182   negate w@(W8# x)  = 
183      if x' ==# 0# 
184       then w
185       else W8# (int2Word# (0x100# -# x'))
186      where
187       x' = word2Int# x
188   abs x         = x
189   signum        = signumReal
190   fromInteger (J# a# s# d#) = W8# (wordToWord8# (integer2Word# a# s# d#))
191   fromInt       = intToWord8
192
193 instance Bounded Word8 where
194   minBound = 0
195   maxBound = 0xff
196
197 instance Real Word8 where
198   toRational x = toInteger x % 1
199
200 -- Note: no need to mask results here 
201 -- as they cannot overflow.
202 instance Integral Word8 where
203   div  (W8# x)  (W8# y)   = W8# (x `quotWord#` y)
204   quot (W8# x)  (W8# y)   = W8# (x `quotWord#` y)
205   rem  (W8# x)  (W8# y)   = W8# (x `remWord#` y)
206   mod  (W8# x)  (W8# y)   = W8# (x `remWord#` y)
207   quotRem (W8# x) (W8# y) = (W8# (x `quotWord#` y), W8# (x `remWord#` y))
208   divMod  (W8# x) (W8# y) = (W8# (x `quotWord#` y), W8# (x `remWord#` y))
209   toInteger (W8# x)       = word2Integer# x
210   toInt x                 = word8ToInt x
211
212 instance Ix Word8 where
213     range (m,n)          = [m..n]
214     index b@(m,n) i
215            | inRange b i = word8ToInt (i-m)
216            | otherwise   = error (showString "Ix{Word8}.index: Index " .
217                                   showParen True (showsPrec 0 i) .
218                                   showString " out of range " $
219                                   showParen True (showsPrec 0 b) "")
220     inRange (m,n) i      = m <= i && i <= n
221
222 instance Enum Word8 where
223     toEnum    (I# i)  = W8# (intToWord8# i)
224     fromEnum  (W8# w) = I# (word2Int# w)
225     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Word8)]
226     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Word8)]
227                        where last = if d < c then minBound else maxBound
228
229 instance Read Word8 where
230     readsPrec p = readDec
231
232 instance Show Word8 where
233     showsPrec p = showInt
234
235 --
236 -- Word8s are represented by an (unboxed) 32-bit Word.
237 -- The invariant is that the upper 24 bits are always zeroed out.
238 --
239 instance Bits Word8 where
240   (W8# x)  .&.  (W8# y)    = W8# (x `and#` y)
241   (W8# x)  .|.  (W8# y)    = W8# (x `or#` y)
242   (W8# x) `xor` (W8# y)    = W8# (x `xor#` y)
243   complement (W8# x)       = W8# (x `xor#` int2Word# 0xff#)
244   shift (W8# x#) i@(I# i#)
245         | i > 0     = W8# (wordToWord8# (shiftL# x# i#))
246         | otherwise = W8# (wordToWord8# (shiftRL# x# (negateInt# i#)))
247   w@(W8# x)  `rotate` (I# i)
248         | i ==# 0#    = w
249         | i ># 0#     = W8# ((wordToWord8# (shiftL# x i')) `or#`
250                              (shiftRL# (x `and#` 
251                                         (int2Word# (0x100# -# pow2# i2)))
252                                        i2))
253         | otherwise = rotate w (I# (8# +# i))
254           where
255            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
256            i2 = 8# -# i'
257
258   bit (I# i#)
259         | i# >=# 0# && i# <=# 7# = W8# (wordToWord8# (shiftL# (int2Word# 1#) i#))
260         | otherwise = 0 -- We'll be overbearing, for now..
261
262   setBit x i    = x .|. bit i
263   clearBit x i  = x .&. complement (bit i)
264   complementBit x i = x `xor` bit i
265
266   testBit (W8# x#) (I# i#)
267     | i# <# 8# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
268     | otherwise             = False -- for now, this is really an error.
269
270   bitSize  _    = 8
271   isSigned _    = False
272
273 pow2# :: Int# -> Int#
274 pow2# x# = word2Int# (shiftL# (int2Word# 1#) x#)
275
276 pow2_64# :: Int# -> Int64#
277 pow2_64# x# = word64ToInt64# (shiftL64# (wordToWord64# (int2Word# 1#)) x#)
278
279 sizeofWord8 :: Word32
280 sizeofWord8 = 1
281
282 \end{code}
283
284 \subsection[Word16]{The @Word16@ interface}
285
286 The double byte type @Word16@ is represented in the Haskell
287 heap by boxing up a machine word, @Word#@. An invariant
288 for this representation is that only the lower 16 bits are
289 `active', any bits above are {\em always} zeroed out.
290 A consequence of this is that operations that could possibly
291 overflow have to mask out anything above the lower two bytes
292 before putting together the resulting @Word16@.
293
294 \begin{code}
295 data Word16 = W16# Word#
296 instance CCallable Word16
297 instance CReturnable Word16
298
299 word16ToWord32 (W16# x) = W32# x
300 word32ToWord16 (W32# x) = W16# (wordToWord16# x)
301
302 -- mask out upper 16 bits.
303 intToWord16# :: Int# -> Word#
304 intToWord16# i# = ((int2Word# i#) `and#` (int2Word# 0xffff#))
305
306 wordToWord16# :: Word# -> Word#
307 wordToWord16# w# = w# `and#` (int2Word# 0xffff#)
308
309 instance Eq  Word16    where 
310   (W16# x) == (W16# y) = x `eqWord#` y
311   (W16# x) /= (W16# y) = x `neWord#` y
312
313 instance Ord Word16     where
314   compare (W16# x#) (W16# y#) = compareWord# x# y#
315   (<)  (W16# x) (W16# y)      = x `ltWord#` y
316   (<=) (W16# x) (W16# y)      = x `leWord#` y
317   (>=) (W16# x) (W16# y)      = x `geWord#` y
318   (>)  (W16# x) (W16# y)      = x `gtWord#` y
319   max x@(W16# x#) y@(W16# y#) = 
320      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
321   min x@(W16# x#) y@(W16# y#) =
322      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
323
324 instance Num Word16 where
325   (W16# x) + (W16# y) = 
326        W16# (intToWord16# (word2Int# x +# word2Int# y))
327   (W16# x) - (W16# y) = 
328        W16# (intToWord16# (word2Int# x -# word2Int# y))
329   (W16# x) * (W16# y) = 
330        W16# (intToWord16# (word2Int# x *# word2Int# y))
331   negate w@(W16# x)  = 
332        if x' ==# 0# 
333         then w
334         else W16# (int2Word# (0x10000# -# x'))
335        where
336         x' = word2Int# x
337   abs x         = x
338   signum        = signumReal
339   fromInteger (J# a# s# d#) = W16# (wordToWord16# (integer2Word# a# s# d#))
340   fromInt       = intToWord16
341
342 instance Bounded Word16 where
343   minBound = 0
344   maxBound = 0xffff
345
346 instance Real Word16 where
347   toRational x = toInteger x % 1
348
349 instance Integral Word16 where
350   div  (W16# x)  (W16# y)   = W16# (x `quotWord#` y)
351   quot (W16# x)  (W16# y)   = W16# (x `quotWord#` y)
352   rem  (W16# x)  (W16# y)   = W16# (x `remWord#` y)
353   mod  (W16# x)  (W16# y)   = W16# (x `remWord#` y)
354   quotRem (W16# x) (W16# y) = (W16# (x `quotWord#` y), W16# (x `remWord#` y))
355   divMod  (W16# x) (W16# y) = (W16# (x `quotWord#` y), W16# (x `remWord#` y))
356   toInteger (W16# x)        = word2Integer# x
357   toInt x                   = word16ToInt x
358
359 instance Ix Word16 where
360   range (m,n)          = [m..n]
361   index b@(m,n) i
362          | inRange b i = word16ToInt (i - m)
363          | otherwise   = error (showString "Ix{Word16}.index: Index " .
364                                 showParen True (showsPrec 0 i) .
365                                 showString " out of range " $
366                                 showParen True (showsPrec 0 b) "")
367   inRange (m,n) i      = m <= i && i <= n
368
369 instance Enum Word16 where
370   toEnum    (I# i)   = W16# (intToWord16# i)
371   fromEnum  (W16# w) = I# (word2Int# w)
372   enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Word16)]
373   enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Word16)]
374                        where last = if d < c then minBound else maxBound
375
376 instance Read Word16 where
377   readsPrec p = readDec
378
379 instance Show Word16 where
380   showsPrec p = showInt
381
382 instance Bits Word16 where
383   (W16# x)  .&.  (W16# y)  = W16# (x `and#` y)
384   (W16# x)  .|.  (W16# y)  = W16# (x `or#` y)
385   (W16# x) `xor` (W16# y)  = W16# (x `xor#` y)
386   complement (W16# x)      = W16# (x `xor#` int2Word# 0xffff#)
387   shift (W16# x#) i@(I# i#)
388         | i > 0     = W16# (wordToWord16# (shiftL# x# i#))
389         | otherwise = W16# (shiftRL# x# (negateInt# i#))
390   w@(W16# x)  `rotate` (I# i)
391         | i ==# 0#    = w
392         | i ># 0#     = W16# ((wordToWord16# (shiftL# x i')) `or#`
393                               (shiftRL# (x `and#` 
394                                          (int2Word# (0x10000# -# pow2# i2)))
395                                         i2))
396         | otherwise = rotate w (I# (16# +# i'))
397           where
398            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
399            i2 = 16# -# i'
400   bit (I# i#)
401         | i# >=# 0# && i# <=# 15# = W16# (shiftL# (int2Word# 1#) i#)
402         | otherwise = 0 -- We'll be overbearing, for now..
403
404   setBit x i    = x .|. bit i
405   clearBit x i  = x .&. complement (bit i)
406   complementBit x i = x `xor` bit i
407
408   testBit (W16# x#) (I# i#)
409     | i# <# 16# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
410     | otherwise             = False -- for now, this is really an error.
411
412   bitSize  _    = 16
413   isSigned _    = False
414
415
416 sizeofWord16 :: Word32
417 sizeofWord16 = 2
418
419 \end{code}
420
421 \subsection[Word32]{The @Word32@ interface}
422
423 The quad byte type @Word32@ is represented in the Haskell
424 heap by boxing up a machine word, @Word#@. An invariant
425 for this representation is that any bits above the lower
426 32 are {\em always} zeroed out. A consequence of this is that
427 operations that could possibly overflow have to mask
428 the result before building the resulting @Word16@.
429
430 \begin{code}
431 data Word32 = W32# Word#
432
433 instance CCallable Word32
434 instance CReturnable Word32
435
436 instance Eq  Word32    where 
437   (W32# x) == (W32# y) = x `eqWord#` y
438   (W32# x) /= (W32# y) = x `neWord#` y
439
440 instance Ord Word32    where
441   compare (W32# x#) (W32# y#) = compareWord# x# y#
442   (<)  (W32# x) (W32# y)      = x `ltWord#` y
443   (<=) (W32# x) (W32# y)      = x `leWord#` y
444   (>=) (W32# x) (W32# y)      = x `geWord#` y
445   (>)  (W32# x) (W32# y)      = x `gtWord#` y
446   max x@(W32# x#) y@(W32# y#) = 
447      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
448   min x@(W32# x#) y@(W32# y#) =
449      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
450
451 instance Num Word32 where
452   (W32# x) + (W32# y) = 
453        W32# (intToWord32# (word2Int# x +# word2Int# y))
454   (W32# x) - (W32# y) =
455        W32# (intToWord32# (word2Int# x -# word2Int# y))
456   (W32# x) * (W32# y) = 
457        W32# (intToWord32# (word2Int# x *# word2Int# y))
458 #if WORD_SIZE_IN_BYTES == 8
459   negate w@(W32# x)  = 
460       if x' ==# 0#
461        then w
462        else W32# (intToWord32# (0x100000000# -# x'))
463        where
464         x' = word2Int# x
465 #else
466   negate (W32# x)  = W32# (intToWord32# (negateInt# (word2Int# x)))
467 #endif
468   abs x           = x
469   signum          = signumReal
470   fromInteger (J# a# s# d#) = W32# (integer2Word# a# s# d#)
471   fromInt (I# x)  = W32# (intToWord32# x)
472     -- ToDo: restrict fromInt{eger} range.
473
474 intToWord32#  :: Int#  -> Word#
475 wordToWord32# :: Word# -> Word#
476
477 #if WORD_SIZE_IN_BYTES == 8
478 intToWord32#  i# = (int2Word# i#) `and#` (int2Word# 0xffffffff)
479 wordToWord32# w# = w# `and#` (int2Word# 0xffffffff)
480 #else
481 intToWord32#  i# = int2Word# i#
482 wordToWord32# w# = w#
483
484 #endif
485
486 instance Bounded Word32 where
487     minBound = 0
488 #if WORD_SIZE_IN_BYTES == 8
489     maxBound = 0xffffffff
490 #else
491     maxBound = minBound - 1
492 #endif
493
494 instance Real Word32 where
495     toRational x = toInteger x % 1
496
497 instance Integral Word32 where
498     div  x y           =  quotWord32 x y
499     quot x y           =  quotWord32 x y
500     rem  x y           =  remWord32 x y
501     mod  x y           =  remWord32 x y
502     quotRem a b        = (a `quotWord32` b, a `remWord32` b)
503     divMod x y         = quotRem x y
504     toInteger (W32# x) = word2Integer# x
505     toInt     (W32# x) = I# (word2Int# x)
506
507 {-# INLINE quotWord32 #-}
508 {-# INLINE remWord32  #-}
509 (W32# x) `quotWord32` (W32# y) = W32# (x `quotWord#` y)
510 (W32# x) `remWord32`  (W32# y) = W32# (x `remWord#`  y)
511
512 instance Ix Word32 where
513     range (m,n)          = [m..n]
514     index b@(m,n) i
515            | inRange b i = word32ToInt (i - m)
516            | otherwise   = error (showString "Ix{Word32}.index: Index " .
517                                   showParen True (showsPrec 0 i) .
518                                   showString " out of range " $
519                                   showParen True (showsPrec 0 b) "")
520     inRange (m,n) i      = m <= i && i <= n
521
522 instance Enum Word32 where
523     toEnum                  = intToWord32
524     fromEnum                = word32ToInt   -- lossy, don't use.
525     enumFrom w              = eft32 w 1
526     enumFromTo   w1 w2      = eftt32 w1 1 (> w2)
527     enumFromThen w1 w2      = eftt32 w1 (w2 - w1) (>last)
528         where 
529          last
530           | w1 < w2   = maxBound::Word32
531           | otherwise = minBound
532
533 eftt32 :: Word32 -> Word32 -> (Word32->Bool) -> [Word32]
534 eftt32 now step done = go now
535   where
536    go now
537      | done now  = []
538      | otherwise = now : go (now+step)
539
540 eft32 :: Word32 -> Word32 -> [Word32]
541 eft32 now step = go now
542   where 
543    go x
544     | x == maxBound = [x]
545     | otherwise     = x:go (x+step)
546
547 instance Read Word32 where
548     readsPrec p = readDec
549
550 instance Show Word32 where
551     showsPrec p = showInt
552
553 instance Bits Word32 where
554   (W32# x)  .&.  (W32# y)  = W32# (x `and#` y)
555   (W32# x)  .|.  (W32# y)  = W32# (x `or#` y)
556   (W32# x) `xor` (W32# y)  = W32# (x `xor#` y)
557   complement (W32# x)      = W32# (x `xor#` mb#) where (W32# mb#) = maxBound
558   shift (W32# x) i@(I# i#)
559         | i > 0     = W32# (wordToWord32# (shiftL# x i#))
560         | otherwise = W32# (shiftRL# x (negateInt# i#))
561   w@(W32# x)  `rotate` (I# i)
562         | i ==# 0#    = w
563         | i ># 0#     = W32# ((wordToWord32# (shiftL# x i')) `or#`
564                               (shiftRL# (x `and#` 
565                                         (int2Word# (word2Int# maxBound# -# pow2# i2 +# 1#)))
566                                      i2))
567         | otherwise = rotate w (I# (32# +# i))
568           where
569            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
570            i2 = 32# -# i'
571            (W32# maxBound#) = maxBound
572
573   bit (I# i#)
574         | i# >=# 0# && i# <=# 31# = W32# (shiftL# (int2Word# 1#) i#)
575         | otherwise = 0 -- We'll be overbearing, for now..
576
577   setBit x i        = x .|. bit i
578   clearBit x i      = x .&. complement (bit i)
579   complementBit x i = x `xor` bit i
580
581   testBit (W32# x#) (I# i#)
582     | i# <# 32# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
583     | otherwise             = False -- for now, this is really an error.
584   bitSize  _        = 32
585   isSigned _        = False
586
587 sizeofWord32 :: Word32
588 sizeofWord32 = 4
589 \end{code}
590
591 \subsection[Word64]{The @Word64@ interface}
592
593 \begin{code}
594 #if WORD_SIZE_IN_BYTES == 8
595 data Word64 = W64# Word#
596
597 word32ToWord64 :: Word32 -> Word64
598 word32ToWord64 (W32 w#) = W64# w#
599
600 wordToWord32# :: Word# -> Word#
601 wordToWord32# w# = w# `and#` (case (maxBound::Word32) of W# x# -> x#)
602
603 word64ToWord32 :: Word64 -> Word32
604 word64ToWord32 (W64# w#) = W32# (wordToWord32# w#)
605
606 wordToWord64# w# = w#
607 word64ToWord# w# = w#
608
609 instance Eq  Word64     where 
610   (W64# x) == (W64# y) = x `eqWord#` y
611   (W64# x) /= (W64# y) = x `neWord#` y
612
613 instance Ord Word64     where 
614   compare (W64# x#) (W64# y#) = compareWord# x# y#
615   (<)  (W64# x) (W64# y)      = x `ltWord#` y
616   (<=) (W64# x) (W64# y)      = x `leWord#` y
617   (>=) (W64# x) (W64# y)      = x `geWord#` y
618   (>)  (W64# x) (W64# y)      = x `gtWord#` y
619   max x@(W64# x#) y@(W64# y#) = 
620      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
621   min x@(W64# x#) y@(W64# y#) =
622      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
623
624 instance Num Word64 where
625   (W64# x) + (W64# y) = 
626       W64# (intToWord64# (word2Int# x +# word2Int# y))
627   (W64# x) - (W64# y) = 
628       W64# (intToWord64# (word2Int# x -# word2Int# y))
629   (W64# x) * (W64# y) = 
630       W64# (intToWord64# (word2Int# x *# word2Int# y))
631   negate w@(W64# x)  = 
632      if x' ==# 0# 
633       then w
634       else W64# (int2Word# (0x100# -# x'))
635      where
636       x' = word2Int# x
637   abs x         = x
638   signum        = signumReal
639   fromInteger (J# a# s# d#) = W64# (integer2Word# a# s# d#)
640   fromInt       = intToWord64
641
642 instance Bounded Word64 where
643   minBound = 0
644   maxBound = minBound - 1
645
646 instance Real Word64 where
647   toRational x = toInteger x % 1
648
649 -- Note: no need to mask results here 
650 -- as they cannot overflow.
651 instance Integral Word64 where
652   div  (W64# x)  (W64# y)   = W64# (x `quotWord#` y)
653   quot (W64# x)  (W64# y)   = W64# (x `quotWord#` y)
654   rem  (W64# x)  (W64# y)   = W64# (x `remWord#` y)
655   mod  (W64# x)  (W64# y)   = W64# (x `remWord#` y)
656   quotRem (W64# x) (W64# y) = (W64# (x `quotWord#` y), W64# (x `remWord#` y))
657   divMod  (W64# x) (W64# y) = (W64# (x `quotWord#` y), W64# (x `remWord#` y))
658   toInteger (W64# x)        = word2Integer# x
659   toInt x                   = word64ToInt x
660
661 instance Ix Word64 where
662     range (m,n)          = [m..n]
663     index b@(m,n) i
664            | inRange b i = word64ToInt (i-m)
665            | otherwise   = error (showString "Ix{Word64}.index: Index " .
666                                   showParen True (showsPrec 0 i) .
667                                   showString " out of range " $
668                                   showParen True (showsPrec 0 b) "")
669     inRange (m,n) i      = m <= i && i <= n
670
671 instance Enum Word64 where
672     toEnum    (I# i)        = W64# (intToWord# i)
673     fromEnum  (W64# w)      = I# (word2Int# w)    -- lossy, don't use.
674     enumFrom w              = eft64 w 1
675     enumFromTo   w1 w2      = eftt64 w1 1 (> w2)
676     enumFromThen w1 w2      = eftt64 w1 (w2 - w1) (>last)
677         where 
678          last
679           | w1 < w2   = maxBound::Word64
680           | otherwise = minBound
681
682 instance Read Word64 where
683     readsPrec p = readDec
684
685 instance Show Word64 where
686     showsPrec p = showInt
687
688
689 instance Bits Word64 where
690   (W64# x)  .&.  (W64# y)    = W64# (x `and#` y)
691   (W64# x)  .|.  (W64# y)    = W64# (x `or#` y)
692   (W64# x) `xor` (W64# y)    = W64# (x `xor#` y)
693   complement (W64# x)        = W64# (x `xor#` (case (maxBound::Word64) of W64# x# -> x#))
694   shift (W64# x#) i@(I# i#)
695         | i > 0     = W64# (shiftL# x# i#)
696         | otherwise = W64# (shiftRL# x# (negateInt# i#))
697
698   w@(W64# x)  `rotate` (I# i)
699         | i ==# 0#    = w
700         | i ># 0#     = W64# (shiftL# x i') `or#`
701                               (shiftRL# (x `and#` 
702                                         (int2Word# (word2Int# maxBound# -# pow2# i2 +# 1#)))
703                                      i2))
704         | otherwise = rotate w (I# (64# +# i))
705           where
706            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
707            i2 = 64# -# i'
708            (W64# maxBound#) = maxBound
709
710   bit (I# i#)
711         | i# >=# 0# && i# <=# 63# = W64# (shiftL# (int2Word# 1#) i#)
712         | otherwise = 0 -- We'll be overbearing, for now..
713
714   setBit x i    = x .|. bit i
715   clearBit x i  = x .&. complement (bit i)
716   complementBit x i = x `xor` bit i
717
718   testBit (W64# x#) (I# i#)
719     | i# <# 64# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
720     | otherwise              = False -- for now, this is really an error.
721
722   bitSize  _    = 64
723   isSigned _    = False
724
725 #else
726 --defined in PrelCCall: data Word64 = W64 Word64# deriving (Eq, Ord, Bounded)
727
728 -- for completeness sake
729 word32ToWord64 :: Word32 -> Word64
730 word32ToWord64 (W32# w#) = W64# (wordToWord64# w#)
731
732 word64ToWord32 :: Word64 -> Word32
733 word64ToWord32 (W64# w#) = W32# (word64ToWord# w#)
734
735 word64ToInteger :: Word64 -> Integer
736 word64ToInteger (W64# w#) = word64ToInteger# w#
737
738 word64ToInt :: Word64 -> Int
739 word64ToInt w = 
740    case w `quotRem` 0x100000000 of 
741      (h,l) -> toInt (word64ToWord32 l)
742
743 intToWord64# :: Int# -> Word64#
744 intToWord64# i# = wordToWord64# (int2Word# i#)
745
746 intToWord64 :: Int -> Word64
747 intToWord64 (I# i#) = W64# (intToWord64# i#)
748
749 integerToWord64 :: Integer -> Word64
750 integerToWord64 (J# a# s# d#) = W64# (integerToWord64# a# s# d#)
751
752 instance Show Word64 where
753   showsPrec p x = showsPrec p (word64ToInteger x)
754
755 instance Read Word64 where
756   readsPrec p s = [ (integerToWord64 x,r) | (x,r) <- readDec s ]
757
758 instance Eq  Word64     where 
759   (W64# x) == (W64# y) = x `eqWord64#` y
760   (W64# x) /= (W64# y) = not (x `eqWord64#` y)
761
762 instance Ord Word64     where 
763   compare (W64# x#) (W64# y#) = compareWord64# x# y#
764   (<)  (W64# x) (W64# y)      = x `ltWord64#` y
765   (<=) (W64# x) (W64# y)      = x `leWord64#` y
766   (>=) (W64# x) (W64# y)      = x `geWord64#` y
767   (>)  (W64# x) (W64# y)      = x `gtWord64#` y
768   max x@(W64# x#) y@(W64# y#) = 
769      case (compareWord64# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
770   min x@(W64# x#) y@(W64# y#) =
771      case (compareWord64# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
772
773 instance Num Word64 where
774   (W64# x) + (W64# y) = 
775       W64# (int64ToWord64# (word64ToInt64# x `plusInt64#` word64ToInt64# y))
776   (W64# x) - (W64# y) = 
777       W64# (int64ToWord64# (word64ToInt64# x `minusInt64#` word64ToInt64# y))
778   (W64# x) * (W64# y) = 
779       W64# (int64ToWord64# (word64ToInt64# x `timesInt64#` word64ToInt64# y))
780   negate w
781      | w == 0     = w
782      | otherwise  = maxBound - w
783
784   abs x         = x
785   signum        = signumReal
786   fromInteger i = integerToWord64 i
787   fromInt       = intToWord64
788
789 instance Bounded Word64 where
790   minBound = 0
791   maxBound = minBound - 1
792
793 instance Real Word64 where
794   toRational x = toInteger x % 1
795
796 -- Note: no need to mask results here 
797 -- as they cannot overflow.
798 instance Integral Word64 where
799   div  (W64# x)  (W64# y)   = W64# (x `quotWord64#` y)
800   quot (W64# x)  (W64# y)   = W64# (x `quotWord64#` y)
801   rem  (W64# x)  (W64# y)   = W64# (x `remWord64#` y)
802   mod  (W64# x)  (W64# y)   = W64# (x `remWord64#` y)
803   quotRem (W64# x) (W64# y) = (W64# (x `quotWord64#` y), W64# (x `remWord64#` y))
804   divMod  (W64# x) (W64# y) = (W64# (x `quotWord64#` y), W64# (x `remWord64#` y))
805   toInteger w64             = word64ToInteger w64
806   toInt x                   = word64ToInt x
807
808
809 instance Ix Word64 where
810     range (m,n)          = [m..n]
811     index b@(m,n) i
812            | inRange b i = word64ToInt (i-m)
813            | otherwise   = error (showString "Ix{Word64}.index: Index " .
814                                   showParen True (showsPrec 0 i) .
815                                   showString " out of range " $
816                                   showParen True (showsPrec 0 b) "")
817     inRange (m,n) i      = m <= i && i <= n
818
819 instance Enum Word64 where
820     toEnum    (I# i)        = W64# (intToWord64# i)
821     fromEnum  (W64# w)      = I# (word2Int# (word64ToWord# w))  -- lossy, don't use.
822     enumFrom w              = eft64 w 1
823     enumFromTo   w1 w2      = eftt64 w1 1 (> w2)
824     enumFromThen w1 w2      = eftt64 w1 (w2 - w1) (>last)
825         where 
826          last
827           | w1 < w2   = maxBound::Word64
828           | otherwise = minBound
829
830 instance Bits Word64 where
831   (W64# x)  .&.  (W64# y)    = W64# (x `and64#` y)
832   (W64# x)  .|.  (W64# y)    = W64# (x `or64#` y)
833   (W64# x) `xor` (W64# y)    = W64# (x `xor64#` y)
834   complement (W64# x)        = W64# (x `xor64#` (case (maxBound::Word64) of W64# x# -> x#))
835   shift (W64# x#) i@(I# i#)
836         | i > 0     = W64# (shiftL64# x# i#)
837         | otherwise = W64# (shiftRL64# x# (negateInt# i#))
838
839   w@(W64# x)  `rotate` (I# i)
840         | i ==# 0#    = w
841         | i ># 0#     = W64# ((shiftL64# x i') `or64#`
842                               (shiftRL64# (x `and64#` 
843                                            (int64ToWord64# ((word64ToInt64# maxBound#) `minusInt64#` 
844                                                            (pow2_64# i2 `plusInt64#` (intToInt64# 1#))))))
845                                      i2)
846         | otherwise = rotate w (I# (64# +# i))
847           where
848            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
849            i2 = 64# -# i'
850            (W64# maxBound#) = maxBound
851
852   bit (I# i#)
853         | i# >=# 0# && i# <=# 63# = W64# (shiftL64# (wordToWord64# (int2Word# 1#)) i#)
854         | otherwise = 0 -- We'll be overbearing, for now..
855
856   setBit x i    = x .|. bit i
857   clearBit x i  = x .&. complement (bit i)
858   complementBit x i = x `xor` bit i
859
860   testBit (W64# x#) (I# i#)
861     | i# <# 64# && i# >=# 0# = (word2Int# (word64ToWord# (x# `and64#` (shiftL64# (wordToWord64# (int2Word# 1#)) i#)))) /=# 0#
862     | otherwise              = False -- for now, this is really an error.
863
864   bitSize  _    = 64
865   isSigned _    = False
866
867 compareWord64# i# j# 
868  | i# `ltWord64#` j# = LT
869  | i# `eqWord64#` j# = EQ
870  | otherwise         = GT
871
872 -- Word64# primop wrappers:
873
874 ltWord64# :: Word64# -> Word64# -> Bool
875 ltWord64# x# y# =  unsafePerformIO $ do
876         v <- _ccall_ stg_ltWord64 x# y# 
877         case (v::Int) of
878           0 -> return False
879           _ -> return True
880       
881 leWord64# :: Word64# -> Word64# -> Bool
882 leWord64# x# y# =  unsafePerformIO $ do
883         v <- _ccall_ stg_leWord64 x# y# 
884         case (v::Int) of
885           0 -> return False
886           _ -> return True
887       
888 eqWord64# :: Word64# -> Word64# -> Bool
889 eqWord64# x# y# =  unsafePerformIO $ do
890         v <- _ccall_ stg_eqWord64 x# y# 
891         case (v::Int) of
892           0 -> return False
893           _ -> return True
894       
895 neWord64# :: Word64# -> Word64# -> Bool
896 neWord64# x# y# =  unsafePerformIO $ do
897         v <- _ccall_ stg_neWord64 x# y# 
898         case (v::Int) of
899           0 -> return False
900           _ -> return True
901       
902 geWord64# :: Word64# -> Word64# -> Bool
903 geWord64# x# y# =  unsafePerformIO $ do
904         v <- _ccall_ stg_geWord64 x# y# 
905         case (v::Int) of
906           0 -> return False
907           _ -> return True
908       
909 gtWord64# :: Word64# -> Word64# -> Bool
910 gtWord64# x# y# =  unsafePerformIO $ do
911         v <- _ccall_ stg_gtWord64 x# y# 
912         case (v::Int) of
913           0 -> return False
914           _ -> return True
915
916 plusInt64# :: Int64# -> Int64# -> Int64#
917 plusInt64# a# b# = 
918   case (unsafePerformIO (_ccall_ stg_plusInt64 a# b#)) of
919     I64# i# -> i#
920
921 minusInt64# :: Int64# -> Int64# -> Int64#
922 minusInt64# a# b# =
923   case (unsafePerformIO (_ccall_ stg_minusInt64 a# b#)) of
924     I64# i# -> i#
925
926 timesInt64# :: Int64# -> Int64# -> Int64#
927 timesInt64# a# b# =
928   case (unsafePerformIO (_ccall_ stg_timesInt64 a# b#)) of
929     I64# i# -> i#
930
931 quotWord64# :: Word64# -> Word64# -> Word64#
932 quotWord64# a# b# =
933   case (unsafePerformIO (_ccall_ stg_quotWord64 a# b#)) of
934     W64# w# -> w#
935
936 remWord64# :: Word64# -> Word64# -> Word64#
937 remWord64# a# b# =
938   case (unsafePerformIO (_ccall_ stg_remWord64 a# b#)) of
939     W64# w# -> w#
940
941 negateInt64# :: Int64# -> Int64#
942 negateInt64# a# =
943   case (unsafePerformIO (_ccall_ stg_negateInt64 a#)) of
944     I64# i# -> i#
945
946 and64# :: Word64# -> Word64# -> Word64#
947 and64# a# b# =
948   case (unsafePerformIO (_ccall_ stg_and64 a# b#)) of
949     W64# w# -> w#
950
951 or64# :: Word64# -> Word64# -> Word64#
952 or64# a# b# =
953   case (unsafePerformIO (_ccall_ stg_or64 a# b#)) of
954     W64# w# -> w#
955
956 xor64# :: Word64# -> Word64# -> Word64#
957 xor64# a# b# = 
958   case (unsafePerformIO (_ccall_ stg_xor64 a# b#)) of
959     W64# w# -> w#
960
961 not64# :: Word64# -> Word64#
962 not64# a# = 
963   case (unsafePerformIO (_ccall_ stg_not64 a#)) of
964     W64# w# -> w#
965
966 shiftL64# :: Word64# -> Int# -> Word64#
967 shiftL64# a# b# =
968   case (unsafePerformIO (_ccall_ stg_shiftL64 a# b#)) of
969     W64# w# -> w#
970
971 shiftRL64# :: Word64# -> Int# -> Word64#
972 shiftRL64# a# b# =
973   case (unsafePerformIO (_ccall_ stg_shiftRL64 a# b#)) of
974     W64# w# -> w#
975
976 word64ToWord# :: Word64# -> Word#
977 word64ToWord# w# =
978   case (unsafePerformIO (_ccall_ stg_word64ToWord w#)) of
979     W# w# -> w#
980       
981 wordToWord64# :: Word# -> Word64#
982 wordToWord64# w# =
983   case (unsafePerformIO (_ccall_ stg_wordToWord64 w#)) of
984     W64# w# -> w#
985
986 word64ToInt64# :: Word64# -> Int64#
987 word64ToInt64# w# =
988   case (unsafePerformIO (_ccall_ stg_word64ToInt64 w#)) of
989     I64# i# -> i#
990
991 int64ToWord64# :: Int64# -> Word64#
992 int64ToWord64# w# =
993   case (unsafePerformIO (_ccall_ stg_int64ToWord64 w#)) of
994     W64# w# -> w#
995
996 intToInt64# :: Int# -> Int64#
997 intToInt64# i# =
998   case (unsafePerformIO (_ccall_ stg_intToInt64 i#)) of
999     I64# i# -> i#
1000       
1001 #endif
1002
1003 sizeofWord64 :: Word32
1004 sizeofWord64 = 8
1005
1006 -- Enum Word64 helper funs:
1007
1008 eftt64 :: Word64 -> Word64 -> (Word64->Bool) -> [Word64]
1009 eftt64 now step done = go now
1010   where
1011    go now
1012      | done now  = []
1013      | otherwise = now : go (now+step)
1014
1015 eft64 :: Word64 -> Word64 -> [Word64]
1016 eft64 now step = go now
1017   where 
1018    go x
1019     | x == maxBound = [x]
1020     | otherwise     = x:go (x+step)
1021 \end{code}
1022
1023
1024
1025 The Hugs-GHC extension libraries provide functions for going between
1026 Int and the various (un)signed ints. Here we provide the same for
1027 the GHC specific Word type:
1028
1029 \begin{code}
1030 wordToWord8  :: Word -> Word8
1031 word8ToWord  :: Word8 -> Word
1032 wordToWord16 :: Word -> Word16
1033 word16ToWord :: Word16 -> Word
1034 wordToWord32 :: Word -> Word32
1035 word32ToWord :: Word32 -> Word
1036
1037 word8ToWord (W8# w#)   = W# w#
1038 wordToWord8 (W# w#)    = W8# (w# `and#` (case (maxBound::Word8) of W8# x# -> x#))
1039 word16ToWord (W16# w#) = W# w#
1040 wordToWord16 (W# w#)   = W16# (w# `and#` (case (maxBound::Word16) of W16# x# -> x#))
1041 word32ToWord (W32# w#) = W# w#
1042 wordToWord32 (W# w#)   = W32# (w# `and#` (case (maxBound::Word32) of W32# x# -> x#))
1043
1044 wordToWord64  :: Word -> Word64
1045 wordToWord64 (W# w#) = W64# (wordToWord64# w#)
1046
1047 -- lossy on 32-bit platforms, but provided nontheless.
1048 word64ToWord :: Word64 -> Word
1049 word64ToWord (W64# w#) = W# (word64ToWord# w#)
1050
1051 \end{code}
1052
1053
1054 --End of exported definitions
1055
1056 The remainder of this file consists of definitions which are only
1057 used in the implementation.
1058
1059 \begin{code}
1060 signumReal x | x == 0    =  0
1061              | x > 0     =  1
1062              | otherwise = -1
1063
1064 \end{code}
1065
1066 NOTE: the index is in units of the size of the type, *not* bytes.
1067
1068 \begin{code}
1069 indexWord8OffAddr  :: Addr -> Int -> Word8
1070 indexWord8OffAddr (A# a#) (I# i#) = intToWord8 (I# (ord# (indexCharOffAddr# a# i#)))
1071
1072 indexWord8OffForeignObj  :: ForeignObj -> Int -> Word8
1073 indexWord8OffForeignObj (ForeignObj fo#) (I# i#) = intToWord8 (I# (ord# (indexCharOffForeignObj# fo# i#)))
1074
1075 indexWord16OffAddr :: Addr -> Int -> Word16
1076 indexWord16OffAddr a i =
1077 #ifdef WORDS_BIGENDIAN
1078   intToWord16 ( word8ToInt l + (word8ToInt maxBound) * word8ToInt h)
1079 #else
1080   intToWord16 ( word8ToInt h + (word8ToInt maxBound) * word8ToInt l)
1081 #endif
1082  where
1083    byte_idx = i * 2
1084    l = indexWord8OffAddr a byte_idx
1085    h = indexWord8OffAddr a (byte_idx+1)
1086
1087 indexWord16OffForeignObj :: ForeignObj -> Int -> Word16
1088 indexWord16OffForeignObj fo i =
1089 #ifdef WORDS_BIGENDIAN
1090   intToWord16 ( word8ToInt l + (word8ToInt maxBound) * word8ToInt h)
1091 #else
1092   intToWord16 ( word8ToInt h + (word8ToInt maxBound) * word8ToInt l)
1093 #endif
1094  where
1095    byte_idx = i * 2
1096    l = indexWord8OffForeignObj fo byte_idx
1097    h = indexWord8OffForeignObj fo (byte_idx+1)
1098
1099 indexWord32OffAddr :: Addr -> Int -> Word32
1100 indexWord32OffAddr (A# a#) i = wordToWord32 (W# (indexWordOffAddr# a# i'#))
1101  where
1102    -- adjust index to be in Word units, not Word32 ones.
1103   (I# i'#) 
1104 #if WORD_SIZE_IN_BYTES==8
1105    = i `div` 2
1106 #else
1107    = i
1108 #endif
1109
1110 indexWord32OffForeignObj :: ForeignObj -> Int -> Word32
1111 indexWord32OffForeignObj (ForeignObj fo#) i = wordToWord32 (W# (indexWordOffForeignObj# fo# i'#))
1112  where
1113    -- adjust index to be in Word units, not Word32 ones.
1114   (I# i'#) 
1115 #if WORD_SIZE_IN_BYTES==8
1116    = i `div` 2
1117 #else
1118    = i
1119 #endif
1120
1121 indexWord64OffAddr :: Addr -> Int -> Word64
1122 indexWord64OffAddr (A# a#) (I# i#)
1123 #if WORD_SIZE_IN_BYTES==8
1124  = W64# (indexWordOffAddr# a# i#)
1125 #else
1126  = W64# (indexWord64OffAddr# a# i#)
1127 #endif
1128
1129 indexWord64OffForeignObj :: ForeignObj -> Int -> Word64
1130 indexWord64OffForeignObj (ForeignObj fo#) (I# i#)
1131 #if WORD_SIZE_IN_BYTES==8
1132  = W64# (indexWordOffForeignObj# fo# i#)
1133 #else
1134  = W64# (indexWord64OffForeignObj# fo# i#)
1135 #endif
1136
1137 \end{code}
1138
1139 Read words out of mutable memory:
1140
1141 \begin{code}
1142 readWord8OffAddr :: Addr -> Int -> IO Word8
1143 readWord8OffAddr a i = _casm_ `` %r=(StgWord8)(((StgWord8*)%0)[(StgInt)%1]); '' a i
1144
1145 readWord8OffForeignObj :: ForeignObj -> Int -> IO Word8
1146 readWord8OffForeignObj fo i = _casm_ `` %r=(StgWord8)(((StgWord8*)%0)[(StgInt)%1]); '' fo i
1147
1148 readWord16OffAddr  :: Addr -> Int -> IO Word16
1149 readWord16OffAddr a i = _casm_ `` %r=(StgWord16)(((StgWord16*)%0)[(StgInt)%1]); '' a i
1150
1151 readWord16OffForeignObj  :: ForeignObj -> Int -> IO Word16
1152 readWord16OffForeignObj fo i = _casm_ `` %r=(StgWord16)(((StgWord16*)%0)[(StgInt)%1]); '' fo i
1153
1154 readWord32OffAddr  :: Addr -> Int -> IO Word32
1155 readWord32OffAddr a i = _casm_ `` %r=(StgWord32)(((StgWord32*)%0)[(StgInt)%1]); '' a i
1156
1157 readWord32OffForeignObj  :: ForeignObj -> Int -> IO Word32
1158 readWord32OffForeignObj fo i = _casm_ `` %r=(StgWord32)(((StgWord32*)%0)[(StgInt)%1]); '' fo i
1159
1160 readWord64OffAddr  :: Addr -> Int -> IO Word64
1161 #if WORD_SIZE_IN_BYTES==8
1162 readWord64OffAddr a i = _casm_ `` %r=(StgWord)(((StgWord*)%0)[(StgInt)%1]); '' a i
1163 #else
1164 readWord64OffAddr a i = _casm_ `` %r=(StgWord64)(((StgWord64*)%0)[(StgInt)%1]); '' a i
1165 #endif
1166
1167 readWord64OffForeignObj  :: ForeignObj -> Int -> IO Word64
1168 #if WORD_SIZE_IN_BYTES==8
1169 readWord64OffForeignObj fo i = _casm_ `` %r=(StgWord)(((StgWord*)%0)[(StgInt)%1]); '' fo i
1170 #else
1171 readWord64OffForeignObj fo i = _casm_ `` %r=(StgWord64)(((StgWord64*)%0)[(StgInt)%1]); '' fo i
1172 #endif
1173 \end{code}
1174
1175 Note: we provide primops for the writing via Addrs since that's used
1176 in the IO implementation (a place where we *really* do care about cycles.)
1177
1178 \begin{code}
1179 writeWord8OffAddr  :: Addr -> Int -> Word8  -> IO ()
1180 writeWord8OffAddr (A# a#) (I# i#) (W8# w#) = IO $ \ s# ->
1181       case (writeCharOffAddr# a# i# (chr# (word2Int# w#)) s#) of s2# -> IOok s2# () 
1182
1183 writeWord16OffAddr :: Addr -> Int -> Word16 -> IO ()
1184 writeWord16OffAddr a i e = _casm_ `` (((StgWord16*)%0)[(StgInt)%1])=(StgWord16)%2; '' a i e
1185
1186 writeWord32OffAddr :: Addr -> Int -> Word32 -> IO ()
1187 writeWord32OffAddr (A# a#) i@(I# i#) (W32# w#) = IO $ \ s# ->
1188       case (writeWordOffAddr#  a# i'# w# s#) of s2# -> IOok s2# () 
1189  where
1190    -- adjust index to be in Word units, not Word32 ones.
1191   (I# i'#) 
1192 #if WORD_SIZE_IN_BYTES==8
1193    = i `div` 2
1194 #else
1195    = i
1196 #endif
1197
1198 writeWord64OffAddr :: Addr -> Int -> Word64 -> IO ()
1199 #if WORD_SIZE_IN_BYTES==8
1200 writeWord64OffAddr (A# a#) (I# i#) (W64# w#) = IO $ \ s# ->
1201       case (writeWordOffAddr#  a# i# w# s#) of s2# -> IOok s2# () 
1202 #else
1203 writeWord64OffAddr (A# a#) (I# i#) (W64# w#) = IO $ \ s# ->
1204       case (writeWord64OffAddr#  a# i# w# s#) of s2# -> IOok s2# () 
1205 #endif
1206
1207 writeWord8OffForeignObj  :: ForeignObj -> Int -> Word8  -> IO ()
1208 writeWord8OffForeignObj fo i w = _casm_ `` (((StgWord16*)%0)[(StgInt)%1])=(StgWord16)%2; '' fo i w
1209
1210 writeWord16OffForeignObj :: ForeignObj -> Int -> Word16 -> IO ()
1211 writeWord16OffForeignObj fo i w = _casm_ `` (((StgWord16*)%0)[(StgInt)%1])=(StgWord16)%2; '' fo i w
1212
1213 writeWord32OffForeignObj :: ForeignObj -> Int -> Word32 -> IO ()
1214 writeWord32OffForeignObj fo i w = _casm_ `` (((StgWord16*)%0)[(StgInt)%1])=(StgWord16)%2; '' fo i' w
1215  where
1216    -- adjust index to be in Word units, not Word32 ones.
1217   i' 
1218 #if WORD_SIZE_IN_BYTES==8
1219    = i `div` 2
1220 #else
1221    = i
1222 #endif
1223
1224 writeWord64OffForeignObj :: ForeignObj -> Int -> Word64 -> IO ()
1225 #if WORD_SIZE_IN_BYTES==8
1226 writeWord64OffForeignObj fo i e = _casm_ `` (((StgWord*)%0)[(StgInt)%1])=(StgWord)%2; '' fo i e
1227 #else
1228 writeWord64OffForeignObj fo i e = _casm_ `` (((StgWord64*)%0)[(StgInt)%1])=(StgWord64)%2; '' fo i e
1229 #endif
1230
1231
1232 \end{code}