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