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