[project @ 2001-01-11 17:25:56 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelWord.lhs
1 %
2 % (c) The University of Glasgow, 1997-2000
3 %
4 \section[PrelWord]{Module @PrelWord@}
5
6 \begin{code}
7 {-# OPTIONS -monly-3-regs #-}
8
9 #include "MachDeps.h"
10
11 module PrelWord (
12         Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
13
14         -- SUP: deprecated in the new FFI, subsumed by fromIntegral
15         , intToWord8      -- :: Int     -> Word8
16         , intToWord16     -- :: Int     -> Word16
17         , intToWord32     -- :: Int     -> Word32
18         , intToWord64     -- :: Int     -> Word64
19
20         , integerToWord8  -- :: Integer -> Word8
21         , integerToWord16 -- :: Integer -> Word16
22         , integerToWord32 -- :: Integer -> Word32
23         , integerToWord64 -- :: Integer -> Word64
24
25         , word8ToInt      -- :: Word8   -> Int
26         , word8ToInteger  -- :: Word8   -> Integer
27         , word8ToWord16   -- :: Word8   -> Word16
28         , word8ToWord32   -- :: Word8   -> Word32
29         , word8ToWord64   -- :: Word8   -> Word64
30
31         , word16ToInt     -- :: Word16  -> Int
32         , word16ToInteger -- :: Word16  -> Integer
33         , word16ToWord8   -- :: Word16  -> Word8
34         , word16ToWord32  -- :: Word16  -> Word32
35         , word16ToWord64  -- :: Word16  -> Word64
36
37         , word32ToInt     -- :: Word32  -> Int
38         , word32ToInteger -- :: Word32  -> Integer
39         , word32ToWord8   -- :: Word32  -> Word8
40         , word32ToWord16  -- :: Word32  -> Word16
41         , word32ToWord64  -- :: Word32  -> Word64
42
43         , word64ToInt     -- :: Word64  -> Int
44         , word64ToInteger -- :: Word64  -> Integer
45         , word64ToWord8   -- :: Word64  -> Word8
46         , word64ToWord16  -- :: Word64  -> Word16
47         , word64ToWord32  -- :: Word64  -> Word32
48
49         -- internal stuff
50         , wordToWord8#, wordToWord16#, wordToWord32#, wordToWord64#
51
52         , word64ToInt64#, int64ToWord64#
53         , wordToWord64#, word64ToWord#
54
55         , toEnumError, fromEnumError, succError, predError, divZeroError
56   ) where
57
58 import PrelArr
59 import PrelBits
60 import PrelRead
61 import PrelEnum
62 import PrelReal
63 import PrelNum
64 import PrelBase
65
66 -- ---------------------------------------------------------------------------
67 -- The Word Type
68 -- ---------------------------------------------------------------------------
69
70 -- A Word is an unsigned integral type, with the same number of bits as Int.
71 data Word = W# Word# deriving (Eq, Ord)
72
73 instance CCallable Word
74 instance CReturnable Word
75
76 -- ---------------------------------------------------------------------------
77 -- Coercion functions (DEPRECATED)
78 -- ---------------------------------------------------------------------------
79
80 intToWord8      :: Int     -> Word8
81 intToWord16     :: Int     -> Word16
82 intToWord32     :: Int     -> Word32
83 intToWord64     :: Int     -> Word64
84
85 integerToWord8  :: Integer -> Word8
86 integerToWord16 :: Integer -> Word16
87 integerToWord32 :: Integer -> Word32
88 integerToWord64 :: Integer -> Word64
89
90 word8ToInt      :: Word8   -> Int
91 word8ToInteger  :: Word8   -> Integer
92 word8ToWord16   :: Word8   -> Word16
93 word8ToWord32   :: Word8   -> Word32
94 word8ToWord64   :: Word8   -> Word64
95
96 word16ToInt     :: Word16  -> Int
97 word16ToInteger :: Word16  -> Integer
98 word16ToWord8   :: Word16  -> Word8
99 word16ToWord32  :: Word16  -> Word32
100 word16ToWord64  :: Word16  -> Word64
101
102 word32ToInt     :: Word32  -> Int
103 word32ToInteger :: Word32  -> Integer
104 word32ToWord8   :: Word32  -> Word8
105 word32ToWord16  :: Word32  -> Word16
106 word32ToWord64  :: Word32  -> Word64
107
108 word64ToInt     :: Word64  -> Int
109 word64ToInteger :: Word64  -> Integer
110 word64ToWord8   :: Word64  -> Word8
111 word64ToWord16  :: Word64  -> Word16
112 word64ToWord32  :: Word64  -> Word32
113
114 intToWord8      = word32ToWord8   . intToWord32
115 intToWord16     = word32ToWord16  . intToWord32
116
117 integerToWord8  = fromInteger
118 integerToWord16 = fromInteger
119
120 word8ToInt      = word32ToInt     . word8ToWord32
121 word8ToInteger  = word32ToInteger . word8ToWord32
122
123 word16ToInt     = word32ToInt     . word16ToWord32
124 word16ToInteger = word32ToInteger . word16ToWord32
125
126 #if WORD_SIZE_IN_BYTES > 4
127 intToWord32 (I# x)   = W32# ((int2Word# x) `and#` (case (maxBound::Word32) of W32# x# -> x#))
128 #else
129 intToWord32 (I# x)   = W32# (int2Word# x)
130 #endif
131
132 word32ToInt (W32# x) = I#   (word2Int# x)
133
134 word2Integer :: Word# -> Integer
135 word2Integer w | i >=# 0#   = S# i
136                | otherwise = case word2Integer# w of
137                                 (# s, d #) -> J# s d
138    where i = word2Int# w
139
140 word32ToInteger (W32# x) = word2Integer x
141 integerToWord32 = fromInteger
142
143 -----------------------------------------------------------------------------
144 -- The following rules for fromIntegral remove the need to export specialized
145 -- conversion functions.
146 -----------------------------------------------------------------------------
147
148 {-# RULES
149    "fromIntegral/Int->Word8"        fromIntegral = intToWord8;
150    "fromIntegral/Int->Word16"       fromIntegral = intToWord16;
151    "fromIntegral/Int->Word32"       fromIntegral = intToWord32;
152    "fromIntegral/Int->Word64"       fromIntegral = intToWord64;
153
154    "fromIntegral/Integer->Word8"    fromIntegral = integerToWord8;
155    "fromIntegral/Integer->Word16"   fromIntegral = integerToWord16;
156    "fromIntegral/Integer->Word32"   fromIntegral = integerToWord32;
157    "fromIntegral/Integer->Word64"   fromIntegral = integerToWord64;
158
159    "fromIntegral/Word8->Int"        fromIntegral = word8ToInt;
160    "fromIntegral/Word8->Integer"    fromIntegral = word8ToInteger;
161    "fromIntegral/Word8->Word16"     fromIntegral = word8ToWord16;
162    "fromIntegral/Word8->Word32"     fromIntegral = word8ToWord32;
163    "fromIntegral/Word8->Word64"     fromIntegral = word8ToWord64;
164
165    "fromIntegral/Word16->Int"       fromIntegral = word16ToInt;
166    "fromIntegral/Word16->Integer"   fromIntegral = word16ToInteger;
167    "fromIntegral/Word16->Word8"     fromIntegral = word16ToWord8;
168    "fromIntegral/Word16->Word32"    fromIntegral = word16ToWord32;
169    "fromIntegral/Word16->Word64"    fromIntegral = word16ToWord64;
170
171    "fromIntegral/Word32->Int"       fromIntegral = word32ToInt;
172    "fromIntegral/Word32->Integer"   fromIntegral = word32ToInteger;
173    "fromIntegral/Word32->Word8"     fromIntegral = word32ToWord8;
174    "fromIntegral/Word32->Word16"    fromIntegral = word32ToWord16;
175    "fromIntegral/Word32->Word64"    fromIntegral = word32ToWord64;
176
177    "fromIntegral/Word64->Int"       fromIntegral = word64ToInt;
178    "fromIntegral/Word64->Integer"   fromIntegral = word64ToInteger;
179    "fromIntegral/Word64->Word8"     fromIntegral = word64ToWord8;
180    "fromIntegral/Word64->Word16"    fromIntegral = word64ToWord16;
181    "fromIntegral/Word64->Word32"    fromIntegral = word64ToWord32
182  #-}
183
184 \end{code}
185
186 \subsection[Word8]{The @Word8@ interface}
187
188
189 The byte type @Word8@ is represented in the Haskell
190 heap by boxing up a 32-bit quantity, @Word#@. An invariant
191 for this representation is that the higher 24 bits are
192 *always* zeroed out. A consequence of this is that
193 operations that could possibly overflow have to mask
194 out the top three bytes before building the resulting @Word8@.
195
196 \begin{code}
197 data Word8  = W8# Word#
198
199 instance CCallable Word8
200 instance CReturnable Word8
201
202 word8ToWord32 (W8#  x) = W32# x
203 word8ToWord16 (W8#  x) = W16# x
204 word32ToWord8 (W32# x) = W8# (wordToWord8# x)
205
206 -- mask out upper three bytes.
207 intToWord8# :: Int# -> Word#
208 intToWord8# i# = (int2Word# i#) `and#` (int2Word# 0xff#)
209
210 wordToWord8# :: Word# -> Word#
211 wordToWord8# w# = w# `and#` (int2Word# 0xff#)
212
213 instance Eq  Word8     where 
214   (W8# x) == (W8# y) = x `eqWord#` y
215   (W8# x) /= (W8# y) = x `neWord#` y
216
217 instance Ord Word8     where 
218   compare (W8# x#) (W8# y#) = compareWord# x# y#
219   (<)  (W8# x) (W8# y)      = x `ltWord#` y
220   (<=) (W8# x) (W8# y)      = x `leWord#` y
221   (>=) (W8# x) (W8# y)      = x `geWord#` y
222   (>)  (W8# x) (W8# y)      = x `gtWord#` y
223   max x@(W8# x#) y@(W8# y#) = 
224      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
225   min x@(W8# x#) y@(W8# y#) =
226      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
227
228 -- Helper function, used by Ord Word* instances.
229 compareWord# :: Word# -> Word# -> Ordering
230 compareWord# x# y# 
231  | x# `ltWord#` y# = LT
232  | x# `eqWord#` y# = EQ
233  | otherwise       = GT
234
235 instance Num Word8 where
236   (W8# x) + (W8# y) = 
237       W8# (intToWord8# (word2Int# x +# word2Int# y))
238   (W8# x) - (W8# y) = 
239       W8# (intToWord8# (word2Int# x -# word2Int# y))
240   (W8# x) * (W8# y) = 
241       W8# (intToWord8# (word2Int# x *# word2Int# y))
242   negate w@(W8# x)  = 
243      if x' ==# 0# 
244       then w
245       else W8# (int2Word# (0x100# -# x'))
246      where
247       x' = word2Int# x
248   abs x         = x
249   signum        = signumReal
250   fromInteger (S# i#)    = W8# (wordToWord8# (int2Word# i#))
251   fromInteger (J# s# d#) = W8# (wordToWord8# (integer2Word# s# d#))
252   fromInt       = intToWord8
253
254 instance Bounded Word8 where
255   minBound = 0
256   maxBound = 0xff
257
258 instance Real Word8 where
259   toRational x = toInteger x % 1
260
261 -- Note: no need to mask results here 
262 -- as they cannot overflow.
263 instance Integral Word8 where
264   div  x@(W8# x#)  (W8# y#) 
265     | y# `neWord#` (int2Word# 0#) = W8# (x# `quotWord#` y#)
266     | otherwise                   = divZeroError "div{Word8}" x
267
268   quot x@(W8# x#)  (W8# y#)   
269     | y# `neWord#` (int2Word# 0#) = W8# (x# `quotWord#` y#)
270     | otherwise                   = divZeroError "quot{Word8}" x
271
272   rem  x@(W8# x#)  (W8# y#)
273     | y# `neWord#` (int2Word# 0#) = W8# (x# `remWord#` y#)
274     | otherwise                   = divZeroError "rem{Word8}" x
275
276   mod  x@(W8# x#)  (W8# y#)
277     | y# `neWord#` (int2Word# 0#) = W8# (x# `remWord#` y#)
278     | otherwise                   = divZeroError "mod{Word8}" x
279
280   quotRem (W8# x) (W8# y) = (W8# (x `quotWord#` y), W8# (x `remWord#` y))
281   divMod  (W8# x) (W8# y) = (W8# (x `quotWord#` y), W8# (x `remWord#` y))
282
283   toInteger = toInteger . toInt
284   toInt     = word8ToInt
285
286 instance Ix Word8 where
287     range (m,n)          = [m..n]
288     index b@(m,_) i
289            | inRange b i = word8ToInt (i-m)
290            | otherwise   = indexError b i "Word8"
291     inRange (m,n) i      = m <= i && i <= n
292
293 instance Enum Word8 where
294     succ w          
295       | w == maxBound = succError "Word8"
296       | otherwise     = w+1
297     pred w          
298       | w == minBound = predError "Word8"
299       | otherwise     = w-1
300
301     toEnum   i@(I# i#)  
302       | i >= toInt (minBound::Word8) && i <= toInt (maxBound::Word8) 
303       = W8# (intToWord8# i#)
304       | otherwise
305       = toEnumError "Word8" i (minBound::Word8,maxBound::Word8)
306
307     fromEnum  (W8# w) = I# (word2Int# w)
308
309     enumFrom          = boundedEnumFrom
310     enumFromThen      = boundedEnumFromThen
311
312 instance Read Word8 where
313     readsPrec _ = readDec
314
315 instance Show Word8 where
316     showsPrec p w8 = showsPrec p (word8ToInt w8)
317
318 instance Bits Word8 where
319   (W8# x)  .&.  (W8# y)    = W8# (x `and#` y)
320   (W8# x)  .|.  (W8# y)    = W8# (x `or#` y)
321   (W8# x) `xor` (W8# y)    = W8# (x `xor#` y)
322   complement (W8# x)       = W8# (x `xor#` int2Word# 0xff#)
323   shift (W8# x#) i@(I# i#)
324         | i > 0     = W8# (wordToWord8# (shiftL# x# i#))
325         | otherwise = W8# (wordToWord8# (shiftRL# x# (negateInt# i#)))
326   w@(W8# x)  `rotate` (I# i)
327         | i ==# 0#    = w
328         | i ># 0#     = W8# ((wordToWord8# (shiftL# x i')) `or#`
329                              (shiftRL# (x `and#` 
330                                         (int2Word# (0x100# -# pow2# i2)))
331                                        i2))
332         | otherwise = rotate w (I# (8# +# i))
333           where
334            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
335            i2 = 8# -# i'
336
337   bit (I# i#)
338         | i# >=# 0# && i# <=# 7# = W8# (wordToWord8# (shiftL# (int2Word# 1#) i#))
339         | otherwise = 0 -- We'll be overbearing, for now..
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 pow2_64# :: Int# -> Int64#
352 pow2_64# x# = word64ToInt64# (shiftL64# (wordToWord64# (int2Word# 1#)) x#)
353
354 -- ---------------------------------------------------------------------------
355 -- Word16
356 -- ---------------------------------------------------------------------------
357
358 -- The double byte type @Word16@ is represented in the Haskell
359 -- heap by boxing up a machine word, @Word#@. An invariant
360 -- for this representation is that only the lower 16 bits are
361 -- `active', any bits above are {\em always} zeroed out.
362 -- A consequence of this is that operations that could possibly
363 -- overflow have to mask out anything above the lower two bytes
364 -- before putting together the resulting @Word16@.
365
366 data Word16 = W16# Word#
367
368 instance CCallable Word16
369 instance CReturnable Word16
370
371 word16ToWord8  (W16# x) = W8#  (wordToWord8#  x)
372 word16ToWord32 (W16# x) = W32# x
373
374 word32ToWord16 (W32# x) = W16# (wordToWord16# x)
375
376 -- mask out upper 16 bits.
377 intToWord16# :: Int# -> Word#
378 intToWord16# i# = ((int2Word# i#) `and#` (int2Word# 0xffff#))
379
380 wordToWord16# :: Word# -> Word#
381 wordToWord16# w# = w# `and#` (int2Word# 0xffff#)
382
383 instance Eq  Word16    where 
384   (W16# x) == (W16# y) = x `eqWord#` y
385   (W16# x) /= (W16# y) = x `neWord#` y
386
387 instance Ord Word16     where
388   compare (W16# x#) (W16# y#) = compareWord# x# y#
389   (<)  (W16# x) (W16# y)      = x `ltWord#` y
390   (<=) (W16# x) (W16# y)      = x `leWord#` y
391   (>=) (W16# x) (W16# y)      = x `geWord#` y
392   (>)  (W16# x) (W16# y)      = x `gtWord#` y
393   max x@(W16# x#) y@(W16# y#) = 
394      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
395   min x@(W16# x#) y@(W16# y#) =
396      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
397
398
399
400 instance Num Word16 where
401   (W16# x) + (W16# y) = 
402        W16# (intToWord16# (word2Int# x +# word2Int# y))
403   (W16# x) - (W16# y) = 
404        W16# (intToWord16# (word2Int# x -# word2Int# y))
405   (W16# x) * (W16# y) = 
406        W16# (intToWord16# (word2Int# x *# word2Int# y))
407   negate w@(W16# x)  = 
408        if x' ==# 0# 
409         then w
410         else W16# (int2Word# (0x10000# -# x'))
411        where
412         x' = word2Int# x
413   abs x         = x
414   signum        = signumReal
415   fromInteger (S# i#)    = W16# (wordToWord16# (int2Word# i#))
416   fromInteger (J# s# d#) = W16# (wordToWord16# (integer2Word# s# d#))
417   fromInt       = intToWord16
418
419 instance Bounded Word16 where
420   minBound = 0
421   maxBound = 0xffff
422
423 instance Real Word16 where
424   toRational x = toInteger x % 1
425
426 instance Integral Word16 where
427   div  x@(W16# x#)  (W16# y#)
428    | y# `neWord#` (int2Word# 0#) = W16# (x# `quotWord#` y#)
429    | otherwise                   = divZeroError "div{Word16}" x
430
431   quot x@(W16# x#) (W16# y#)
432    | y# `neWord#`(int2Word# 0#)  = W16# (x# `quotWord#` y#)
433    | otherwise                   = divZeroError "quot{Word16}" x
434
435   rem  x@(W16# x#) (W16# y#)
436    | y# `neWord#` (int2Word# 0#) = W16# (x# `remWord#` y#)
437    | otherwise                   = divZeroError "rem{Word16}" x
438
439   mod  x@(W16# x#)  (W16# y#)
440    | y# `neWord#` (int2Word# 0#) = W16# (x# `remWord#` y#)
441    | otherwise                   = divZeroError "mod{Word16}" x
442
443   quotRem (W16# x) (W16# y) = (W16# (x `quotWord#` y), W16# (x `remWord#` y))
444   divMod  (W16# x) (W16# y) = (W16# (x `quotWord#` y), W16# (x `remWord#` y))
445
446   toInteger = toInteger . toInt
447   toInt     = word16ToInt
448
449 instance Ix Word16 where
450   range (m,n)          = [m..n]
451   index b@(m,_) i
452          | inRange b i = word16ToInt (i - m)
453          | otherwise   = indexError b i "Word16"
454   inRange (m,n) i      = m <= i && i <= n
455
456 instance Enum Word16 where
457     succ w          
458       | w == maxBound = succError "Word16"
459       | otherwise     = w+1
460     pred w          
461       | w == minBound = predError "Word16"
462       | otherwise     = w-1
463
464     toEnum   i@(I# i#)  
465       | i >= toInt (minBound::Word16) && i <= toInt (maxBound::Word16)
466       = W16# (intToWord16# i#)
467       | otherwise
468       = toEnumError "Word16" i (minBound::Word16,maxBound::Word16)
469
470     fromEnum  (W16# w) = I# (word2Int# w)
471     enumFrom     = boundedEnumFrom
472     enumFromThen = boundedEnumFromThen
473
474 instance Read Word16 where
475   readsPrec _ = readDec
476
477 instance Show Word16 where
478   showsPrec p w16 = showsPrec p (word16ToInt w16)
479
480 instance Bits Word16 where
481   (W16# x)  .&.  (W16# y)  = W16# (x `and#` y)
482   (W16# x)  .|.  (W16# y)  = W16# (x `or#` y)
483   (W16# x) `xor` (W16# y)  = W16# (x `xor#` y)
484   complement (W16# x)      = W16# (x `xor#` int2Word# 0xffff#)
485   shift (W16# x#) i@(I# i#)
486         | i > 0     = W16# (wordToWord16# (shiftL# x# i#))
487         | otherwise = W16# (shiftRL# x# (negateInt# i#))
488   w@(W16# x)  `rotate` (I# i)
489         | i ==# 0#    = w
490         | i ># 0#     = W16# ((wordToWord16# (shiftL# x i')) `or#`
491                               (shiftRL# (x `and#` 
492                                          (int2Word# (0x10000# -# pow2# i2)))
493                                         i2))
494         | otherwise = rotate w (I# (16# +# i'))
495           where
496            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
497            i2 = 16# -# i'
498   bit (I# i#)
499         | i# >=# 0# && i# <=# 15# = W16# (shiftL# (int2Word# 1#) i#)
500         | otherwise = 0 -- We'll be overbearing, for now..
501
502   testBit (W16# x#) (I# i#)
503     | i# <# 16# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
504     | otherwise             = False -- for now, this is really an error.
505
506   bitSize  _    = 16
507   isSigned _    = False
508
509 -- ---------------------------------------------------------------------------
510 -- Word32
511 -- ---------------------------------------------------------------------------
512
513 -- The quad byte type @Word32@ is represented in the Haskell
514 -- heap by boxing up a machine word, @Word#@. An invariant
515 -- for this representation is that any bits above the lower
516 -- 32 are {\em always} zeroed out. A consequence of this is that
517 -- operations that could possibly overflow have to mask
518 -- the result before building the resulting @Word16@.
519
520 data Word32 = W32# Word#
521
522 instance CCallable Word32
523 instance CReturnable Word32
524
525 instance Eq  Word32    where 
526   (W32# x) == (W32# y) = x `eqWord#` y
527   (W32# x) /= (W32# y) = x `neWord#` y
528
529 instance Ord Word32    where
530   compare (W32# x#) (W32# y#) = compareWord# x# y#
531   (<)  (W32# x) (W32# y)      = x `ltWord#` y
532   (<=) (W32# x) (W32# y)      = x `leWord#` y
533   (>=) (W32# x) (W32# y)      = x `geWord#` y
534   (>)  (W32# x) (W32# y)      = x `gtWord#` y
535   max x@(W32# x#) y@(W32# y#) = 
536      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
537   min x@(W32# x#) y@(W32# y#) =
538      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
539
540 instance Num Word32 where
541   (W32# x) + (W32# y) = 
542        W32# (intToWord32# (word2Int# x +# word2Int# y))
543   (W32# x) - (W32# y) =
544        W32# (intToWord32# (word2Int# x -# word2Int# y))
545   (W32# x) * (W32# y) = 
546        W32# (intToWord32# (word2Int# x *# word2Int# y))
547 #if WORD_SIZE_IN_BYTES == 8
548   negate w@(W32# x)  = 
549       if x' ==# 0#
550        then w
551        else W32# (intToWord32# (0x100000000# -# x'))
552        where
553         x' = word2Int# x
554 #else
555   negate (W32# x)  = W32# (intToWord32# (negateInt# (word2Int# x)))
556 #endif
557   abs x           = x
558   signum          = signumReal
559   fromInteger (S# i#)    = W32# (intToWord32# i#)
560   fromInteger (J# s# d#) = W32# (wordToWord32# (integer2Word# s# d#))
561   fromInt (I# x)  = W32# (intToWord32# x)
562     -- ToDo: restrict fromInt{eger} range.
563
564 intToWord32#  :: Int#  -> Word#
565 wordToWord32# :: Word# -> Word#
566
567 #if WORD_SIZE_IN_BYTES == 8
568 intToWord32#  i#  = (int2Word# i#) `and#` (int2Word# 0xffffffff#)
569 wordToWord32# w#  = w# `and#` (int2Word# 0xffffffff#)
570 wordToWord64# w#  = w#
571 #else
572 intToWord32#  i# = int2Word# i#
573 wordToWord32# w# = w#
574 #endif
575
576 instance Bounded Word32 where
577     minBound = 0
578 #if WORD_SIZE_IN_BYTES == 8
579     maxBound = 0xffffffff
580 #else
581     maxBound = minBound - 1
582 #endif
583
584 instance Real Word32 where
585     toRational x = toInteger x % 1
586
587 instance Integral Word32 where
588     div  x y 
589       | y /= 0         = quotWord32 x y
590       | otherwise      = divZeroError "div{Word32}" x
591
592     quot x y
593       | y /= 0         = quotWord32 x y
594       | otherwise      = divZeroError "quot{Word32}" x
595
596     rem  x y
597       | y /= 0         = remWord32 x y
598       | otherwise      = divZeroError "rem{Word32}" x
599
600     mod  x y
601       | y /= 0         = remWord32 x y
602       | otherwise      = divZeroError "mod{Word32}" x
603
604     quotRem a b        = (a `quot` b, a `rem` b)
605     divMod x y         = quotRem x y
606
607     toInteger          = word32ToInteger 
608     toInt              = word32ToInt
609
610
611 {-# INLINE quotWord32 #-}
612 {-# INLINE remWord32  #-}
613 remWord32, quotWord32 :: Word32 -> Word32 -> Word32
614 (W32# x) `quotWord32` (W32# y) = W32# (x `quotWord#` y)
615 (W32# x) `remWord32`  (W32# y) = W32# (x `remWord#`  y)
616
617
618 instance Ix Word32 where
619     range (m,n)          = [m..n]
620     index b@(m,_) i
621            | inRange b i = word32ToInt (i - m)
622            | otherwise   = indexError b i "Word32"
623     inRange (m,n) i      = m <= i && i <= n
624
625 instance Enum Word32 where
626     succ w          
627       | w == maxBound = succError "Word32"
628       | otherwise     = w+1
629     pred w          
630       | w == minBound = predError "Word32"
631       | otherwise     = w-1
632
633      -- the toEnum/fromEnum will fail if the mapping isn't legal,
634      -- use the intTo* & *ToInt coercion functions to 'bypass' these range checks.
635     toEnum   x
636       | x >= 0    = intToWord32 x
637       | otherwise
638       = toEnumError "Word32" x (minBound::Word32,maxBound::Word32)
639
640     fromEnum   x
641       | x <= intToWord32 (maxBound::Int)
642       = word32ToInt x
643       | otherwise
644       = fromEnumError "Word32" x 
645
646     enumFrom w           = [w .. maxBound]
647     enumFromTo   w1 w2
648        | w1 <= w2        = eftt32 True{-increasing-} w1 diff_f last
649        | otherwise       = []
650         where
651          last = (> w2)
652          diff_f x = x + 1 
653           
654     enumFromThen w1 w2   = [w1,w2 .. last]
655        where
656          last :: Word32
657          last
658           | w1 <=w2   = maxBound
659           | otherwise = minBound
660
661     enumFromThenTo w1 w2 wend  = eftt32 increasing w1 step_f last
662      where
663        increasing = w1 <= w2
664        diff1 = w2 - w1
665        diff2 = w1 - w2
666        
667        last
668         | increasing = (> wend)
669         | otherwise  = (< wend)
670
671        step_f 
672         | increasing = \ x -> x + diff1
673         | otherwise  = \ x -> x - diff2
674
675 eftt32 :: Bool -> Word32 -> (Word32 -> Word32) -> (Word32-> Bool) -> [Word32]
676 eftt32 increasing init stepper done = go init
677   where
678     go now
679      | done now                    = []
680      | increasing     && now > nxt = [now] -- oflow
681      | not increasing && now < nxt = [now] -- uflow
682      | otherwise                   = now : go nxt
683      where
684       nxt = stepper now 
685
686 instance Read Word32 where
687     readsPrec _ = readDec
688
689 instance Show Word32 where
690     showsPrec p w = showsPrec p (word32ToInteger w)
691
692 instance Bits Word32 where
693   (W32# x)  .&.  (W32# y)  = W32# (x `and#` y)
694   (W32# x)  .|.  (W32# y)  = W32# (x `or#` y)
695   (W32# x) `xor` (W32# y)  = W32# (x `xor#` y)
696   complement (W32# x)      = W32# (x `xor#` mb#) where (W32# mb#) = maxBound
697   shift (W32# x) i@(I# i#)
698         | i > 0     = W32# (wordToWord32# (shiftL# x i#))
699         | otherwise = W32# (shiftRL# x (negateInt# i#))
700   w@(W32# x)  `rotate` (I# i)
701         | i ==# 0#    = w
702         | i ># 0#     = W32# ((wordToWord32# (shiftL# x i')) `or#`
703                               (shiftRL# (x `and#` 
704                                         (int2Word# (word2Int# maxBound# -# pow2# i2 +# 1#)))
705                                      i2))
706         | otherwise = rotate w (I# (32# +# i))
707           where
708            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
709            i2 = 32# -# i'
710            (W32# maxBound#) = maxBound
711
712   bit (I# i#)
713         | i# >=# 0# && i# <=# 31# = W32# (shiftL# (int2Word# 1#) i#)
714         | otherwise = 0 -- We'll be overbearing, for now..
715
716   testBit (W32# x#) (I# i#)
717     | i# <# 32# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
718     | otherwise             = False -- for now, this is really an error.
719   bitSize  _        = 32
720   isSigned _        = False
721
722 -- -----------------------------------------------------------------------------
723 -- Word64
724 -- -----------------------------------------------------------------------------
725
726 #if WORD_SIZE_IN_BYTES == 8
727 data Word64 = W64# Word#
728
729 word32ToWord64 (W32 w#) = W64# w#
730
731 word8ToWord64 (W8# w#) = W64# w#
732 word64ToWord8 (W64# w#) = W8# (w# `and#` (int2Word# 0xff#))
733
734 word16ToWord64 (W16# w#) = W64# w#
735 word64ToWord16 (W64# w#) = W16# (w# `and#` (int2Word# 0xffff#))
736
737 wordToWord32# :: Word# -> Word#
738 wordToWord32# w# = w# `and#` (case (maxBound::Word32) of W# x# -> x#)
739
740 word64ToWord32 :: Word64 -> Word32
741 word64ToWord32 (W64# w#) = W32# (wordToWord32# w#)
742
743 wordToWord64# w# = w#
744 word64ToWord# w# = w#
745
746 instance Eq  Word64     where 
747   (W64# x) == (W64# y) = x `eqWord#` y
748   (W64# x) /= (W64# y) = x `neWord#` y
749
750 instance Ord Word64     where 
751   compare (W64# x#) (W64# y#) = compareWord# x# y#
752   (<)  (W64# x) (W64# y)      = x `ltWord#` y
753   (<=) (W64# x) (W64# y)      = x `leWord#` y
754   (>=) (W64# x) (W64# y)      = x `geWord#` y
755   (>)  (W64# x) (W64# y)      = x `gtWord#` y
756   max x@(W64# x#) y@(W64# y#) = 
757      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
758   min x@(W64# x#) y@(W64# y#) =
759      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
760
761 instance Num Word64 where
762   (W64# x) + (W64# y) = 
763       W64# (intToWord64# (word2Int# x +# word2Int# y))
764   (W64# x) - (W64# y) = 
765       W64# (intToWord64# (word2Int# x -# word2Int# y))
766   (W64# x) * (W64# y) = 
767       W64# (intToWord64# (word2Int# x *# word2Int# y))
768   negate w@(W64# x)  = 
769      if x' ==# 0# 
770       then w
771       else W64# (int2Word# (0x100# -# x'))
772      where
773       x' = word2Int# x
774   abs x         = x
775   signum        = signumReal
776   fromInteger (S# i#)    = W64# (int2Word# i#)
777   fromInteger (J# s# d#) = W64# (integer2Word# s# d#)
778   fromInt       = intToWord64
779
780 -- Note: no need to mask results here 
781 -- as they cannot overflow.
782 instance Integral Word64 where
783   div  x@(W64# x#)  (W64# y#)
784     | y# `neWord#` (int2Word# 0#)  = W64# (x# `quotWord#` y#)
785     | otherwise                    = divZeroError "div{Word64}" x
786
787   quot x@(W64# x#)  (W64# y#)
788     | y# `neWord#` (int2Word# 0#)  = W64# (x# `quotWord#` y#)
789     | otherwise                    = divZeroError "quot{Word64}" x
790
791   rem  x@(W64# x#)  (W64# y#)
792     | y# `neWord#` (int2Word# 0#)  = W64# (x# `remWord#` y#)
793     | otherwise                    = divZeroError "rem{Word64}" x
794
795   mod  (W64# x)  (W64# y)   
796     | y# `neWord#` (int2Word# 0#)  = W64# (x `remWord#` y)
797     | otherwise                    = divZeroError "mod{Word64}" x
798
799   quotRem (W64# x) (W64# y) = (W64# (x `quotWord#` y), W64# (x `remWord#` y))
800   divMod  (W64# x) (W64# y) = (W64# (x `quotWord#` y), W64# (x `remWord#` y))
801
802   toInteger (W64# x)        = word2Integer# x
803   toInt x                   = word64ToInt x
804
805 #else /* WORD_SIZE_IN_BYTES < 8 */
806
807 data Word64 = W64# Word64#
808
809 -- for completeness sake
810 word32ToWord64 (W32# w#) = W64# (wordToWord64# w#)
811 word64ToWord32 (W64# w#) = W32# (word64ToWord# w#)
812
813 word8ToWord64 (W8# w#) = W64# (wordToWord64# w#)
814 word64ToWord8 (W64# w#) = W8# ((word64ToWord# w#) `and#` (int2Word# 0xff#))
815
816 word16ToWord64 (W16# w#) = W64# (wordToWord64# w#)
817 word64ToWord16 (W64# w#) = W16# ((word64ToWord# w#) `and#` (int2Word# 0xffff#))
818
819 word64ToInteger (W64# w#) = 
820   case word64ToInteger# w# of
821     (# s#, p# #) -> J# s# p#
822 word64ToInt w = 
823    case w `quotRem` 0x100000000 of 
824      (_,l) -> toInt (word64ToWord32 l)
825
826 intToWord64# :: Int# -> Word64#
827 intToWord64# i# = wordToWord64# (int2Word# i#)
828
829 intToWord64 (I# i#) = W64# (intToWord64# i#)
830
831 integerToWord64 (S# i#)    = W64# (intToWord64# i#)
832 integerToWord64 (J# s# d#) = W64# (integerToWord64# s# d#)
833
834 instance Eq  Word64     where 
835   (W64# x) == (W64# y) = x `eqWord64#` y
836   (W64# x) /= (W64# y) = not (x `eqWord64#` y)
837
838 instance Ord Word64     where 
839   compare (W64# x#) (W64# y#) = compareWord64# x# y#
840   (<)  (W64# x) (W64# y)      = x `ltWord64#` y
841   (<=) (W64# x) (W64# y)      = x `leWord64#` y
842   (>=) (W64# x) (W64# y)      = x `geWord64#` y
843   (>)  (W64# x) (W64# y)      = x `gtWord64#` y
844   max x@(W64# x#) y@(W64# y#) = 
845      case (compareWord64# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
846   min x@(W64# x#) y@(W64# y#) =
847      case (compareWord64# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
848
849 instance Num Word64 where
850   (W64# x) + (W64# y) = 
851       W64# (int64ToWord64# (word64ToInt64# x `plusInt64#` word64ToInt64# y))
852   (W64# x) - (W64# y) = 
853       W64# (int64ToWord64# (word64ToInt64# x `minusInt64#` word64ToInt64# y))
854   (W64# x) * (W64# y) = 
855       W64# (int64ToWord64# (word64ToInt64# x `timesInt64#` word64ToInt64# y))
856   negate w
857      | w == 0     = w
858      | otherwise  = maxBound - w
859
860   abs x         = x
861   signum        = signumReal
862   fromInteger i = integerToWord64 i
863   fromInt       = intToWord64
864
865 -- Note: no need to mask results here  as they cannot overflow.
866 -- ToDo: protect against div by zero.
867 instance Integral Word64 where
868   div  (W64# x)  (W64# y)   = W64# (x `quotWord64#` y)
869   quot (W64# x)  (W64# y)   = W64# (x `quotWord64#` y)
870   rem  (W64# x)  (W64# y)   = W64# (x `remWord64#` y)
871   mod  (W64# x)  (W64# y)   = W64# (x `remWord64#` y)
872   quotRem (W64# x) (W64# y) = (W64# (x `quotWord64#` y), W64# (x `remWord64#` y))
873   divMod  (W64# x) (W64# y) = (W64# (x `quotWord64#` y), W64# (x `remWord64#` y))
874   toInteger w64             = word64ToInteger w64
875   toInt x                   = word64ToInt x
876
877 compareWord64# :: Word64# -> Word64# -> Ordering
878 compareWord64# i# j# 
879  | i# `ltWord64#` j# = LT
880  | i# `eqWord64#` j# = EQ
881  | otherwise         = GT
882
883 -- Word64# primop wrappers:
884
885 ltWord64# :: Word64# -> Word64# -> Bool
886 ltWord64# x# y# = stg_ltWord64 x# y# /=# 0#
887
888 leWord64# :: Word64# -> Word64# -> Bool
889 leWord64# x# y# = stg_leWord64 x# y# /=# 0#
890
891 eqWord64# :: Word64# -> Word64# -> Bool
892 eqWord64# x# y# = stg_eqWord64 x# y# /=# 0#
893       
894 neWord64# :: Word64# -> Word64# -> Bool
895 neWord64# x# y# = stg_neWord64 x# y# /=# 0#
896       
897 geWord64# :: Word64# -> Word64# -> Bool
898 geWord64# x# y# = stg_geWord64 x# y# /=# 0#
899       
900 gtWord64# :: Word64# -> Word64# -> Bool
901 gtWord64# x# y# = stg_gtWord64 x# y# /=# 0#
902
903 foreign import "stg_intToInt64" unsafe intToInt64# :: Int# -> Int64#
904 foreign import "stg_int64ToWord64" unsafe int64ToWord64# :: Int64# -> Word64#
905 foreign import "stg_word64ToInt64" unsafe word64ToInt64# :: Word64# -> Int64#
906 foreign import "stg_wordToWord64" unsafe wordToWord64# :: Word# -> Word64#
907 foreign import "stg_word64ToWord" unsafe word64ToWord# :: Word64# -> Word#
908 foreign import "stg_negateInt64" unsafe negateInt64# :: Int64# -> Int64#
909 foreign import "stg_remWord64" unsafe remWord64# :: Word64# -> Word64# -> Word64#
910 foreign import "stg_quotWord64" unsafe quotWord64# :: Word64# -> Word64# -> Word64#
911 foreign import "stg_timesInt64" unsafe timesInt64# :: Int64# -> Int64# -> Int64#
912 foreign import "stg_minusInt64" unsafe minusInt64# :: Int64# -> Int64# -> Int64#
913 foreign import "stg_plusInt64" unsafe plusInt64# :: Int64# -> Int64# -> Int64#
914 foreign import "stg_gtWord64" unsafe stg_gtWord64 :: Word64# -> Word64# -> Int#
915 foreign import "stg_geWord64" unsafe stg_geWord64 :: Word64# -> Word64# -> Int#
916 foreign import "stg_neWord64" unsafe stg_neWord64 :: Word64# -> Word64# -> Int#
917 foreign import "stg_eqWord64" unsafe stg_eqWord64 :: Word64# -> Word64# -> Int#
918 foreign import "stg_leWord64" unsafe stg_leWord64 :: Word64# -> Word64# -> Int#
919 foreign import "stg_ltWord64" unsafe stg_ltWord64 :: Word64# -> Word64# -> Int#
920
921 #endif
922
923 instance CCallable   Word64
924 instance CReturnable Word64
925
926 instance Enum Word64 where
927     succ w          
928       | w == maxBound = succError "Word64"
929       | otherwise     = w+1
930     pred w          
931       | w == minBound = predError "Word64"
932       | otherwise     = w-1
933
934     toEnum i
935       | i >= 0    = intToWord64 i
936       | otherwise 
937       = toEnumError "Word64" i (minBound::Word64,maxBound::Word64)
938
939     fromEnum w
940       | w <= intToWord64 (maxBound::Int)
941       = word64ToInt w
942       | otherwise
943       = fromEnumError "Word64" w
944
945     enumFrom e1        = map integerToWord64 [word64ToInteger e1 .. word64ToInteger maxBound]
946     enumFromTo e1 e2   = map integerToWord64 [word64ToInteger e1 .. word64ToInteger e2]
947     enumFromThen e1 e2 = map integerToWord64 [word64ToInteger e1, word64ToInteger e2 .. word64ToInteger last]
948                        where 
949                           last :: Word64
950                           last 
951                            | e2 < e1   = minBound
952                            | otherwise = maxBound
953
954     enumFromThenTo e1 e2 e3 = map integerToWord64 [word64ToInteger e1, word64ToInteger e2 .. word64ToInteger e3]
955
956 instance Show Word64 where
957   showsPrec p x = showsPrec p (word64ToInteger x)
958
959 instance Read Word64 where
960   readsPrec _ s = [ (integerToWord64 x,r) | (x,r) <- readDec s ]
961
962 instance Ix Word64 where
963     range (m,n)          = [m..n]
964     index b@(m,_) i
965            | inRange b i = word64ToInt (i-m)
966            | otherwise   = indexError b i "Word64"
967     inRange (m,n) i      = m <= i && i <= n
968
969 instance Bounded Word64 where
970   minBound = 0
971   maxBound = minBound - 1
972
973 instance Real Word64 where
974   toRational x = toInteger x % 1
975
976 #if WORD_SIZE_IN_BYTES == 8
977
978 instance Bits Word64 where
979   (W64# x)  .&.  (W64# y)    = W64# (x `and#` y)
980   (W64# x)  .|.  (W64# y)    = W64# (x `or#` y)
981   (W64# x) `xor` (W64# y)    = W64# (x `xor#` y)
982   complement (W64# x)        = W64# (x `xor#` (case (maxBound::Word64) of W64# x# -> x#))
983   shift (W64# x#) i@(I# i#)
984         | i > 0     = W64# (shiftL# x# i#)
985         | otherwise = W64# (shiftRL# x# (negateInt# i#))
986
987   w@(W64# x)  `rotate` (I# i)
988         | i ==# 0#    = w
989         | i ># 0#     = W64# (shiftL# x i') `or#`
990                               (shiftRL# (x `and#` 
991                                         (int2Word# (word2Int# maxBound# -# pow2# i2 +# 1#)))
992                                      i2))
993         | otherwise = rotate w (I# (64# +# i))
994           where
995            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
996            i2 = 64# -# i'
997            (W64# maxBound#) = maxBound
998
999   bit (I# i#)
1000         | i# >=# 0# && i# <=# 63# = W64# (shiftL# (int2Word# 1#) i#)
1001         | otherwise = 0 -- We'll be overbearing, for now..
1002
1003   testBit (W64# x#) (I# i#)
1004     | i# <# 64# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
1005     | otherwise              = False -- for now, this is really an error.
1006
1007   bitSize  _    = 64
1008   isSigned _    = False
1009
1010 #else /* WORD_SIZE_IN_BYTES < 8 */
1011
1012 instance Bits Word64 where
1013   (W64# x)  .&.  (W64# y)    = W64# (x `and64#` y)
1014   (W64# x)  .|.  (W64# y)    = W64# (x `or64#` y)
1015   (W64# x) `xor` (W64# y)    = W64# (x `xor64#` y)
1016   complement (W64# x)        = W64# (x `xor64#` (case (maxBound::Word64) of W64# x# -> x#))
1017   shift (W64# x#) i@(I# i#)
1018         | i > 0     = W64# (shiftL64# x# i#)
1019         | otherwise = W64# (shiftRL64# x# (negateInt# i#))
1020
1021   w@(W64# x)  `rotate` (I# i)
1022         | i ==# 0#    = w
1023         | i ># 0#     = W64# ((shiftL64# x i') `or64#`
1024                               (shiftRL64# (x `and64#` 
1025                                            (int64ToWord64# ((word64ToInt64# maxBound#) `minusInt64#` 
1026                                                            (pow2_64# i2 `plusInt64#` (intToInt64# 1#))))))
1027                                      i2)
1028         | otherwise = rotate w (I# (64# +# i))
1029           where
1030            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
1031            i2 = 64# -# i'
1032            (W64# maxBound#) = maxBound
1033
1034   bit (I# i#)
1035         | i# >=# 0# && i# <=# 63# = W64# (shiftL64# (wordToWord64# (int2Word# 1#)) i#)
1036         | otherwise = 0 -- We'll be overbearing, for now..
1037
1038   testBit (W64# x#) (I# i#)
1039     | i# <# 64# && i# >=# 0# = (word2Int# (word64ToWord# (x# `and64#` (shiftL64# (wordToWord64# (int2Word# 1#)) i#)))) /=# 0#
1040     | otherwise              = False -- for now, this is really an error.
1041
1042   bitSize  _    = 64
1043   isSigned _    = False
1044
1045 foreign import "stg_not64"     unsafe not64#    :: Word64# -> Word64#
1046 foreign import "stg_xor64"     unsafe xor64#    :: Word64# -> Word64# -> Word64#
1047 foreign import "stg_or64"      unsafe or64#     :: Word64# -> Word64# -> Word64#
1048 foreign import "stg_and64"     unsafe and64#    :: Word64# -> Word64# -> Word64#
1049 foreign import "stg_shiftRL64" unsafe shiftRL64# :: Word64# -> Int# -> Word64#
1050 foreign import "stg_shiftL64"  unsafe shiftL64#  :: Word64# -> Int# -> Word64#
1051
1052 #endif /* WORD_SIZE_IN_BYTES < 8 */
1053 \end{code}
1054
1055 Misc utils.
1056
1057 \begin{code}
1058 signumReal :: (Ord a, Num a) => a -> a
1059 signumReal x | x == 0    =  0
1060              | x > 0     =  1
1061              | otherwise = -1
1062 \end{code}
1063
1064 Utils for generating friendly error messages.
1065
1066 \begin{code}
1067 toEnumError :: (Show a,Show b) => String -> a -> (b,b) -> c
1068 toEnumError inst_ty tag bnds
1069   = error ("Enum.toEnum{" ++ inst_ty ++ "}: tag " ++
1070            (showParen True (showsPrec 0 tag) $
1071              " is outside of bounds " ++
1072              show bnds))
1073
1074 fromEnumError :: (Show a,Show b) => String -> a -> b
1075 fromEnumError inst_ty tag
1076   = error ("Enum.fromEnum{" ++ inst_ty ++ "}: value " ++
1077            (showParen True (showsPrec 0 tag) $
1078              " is outside of Int's bounds " ++
1079              show (minBound::Int,maxBound::Int)))
1080
1081 succError :: String -> a
1082 succError inst_ty
1083   = error ("Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound")
1084
1085 predError :: String -> a
1086 predError inst_ty
1087   = error ("Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound")
1088
1089 divZeroError :: (Show a) => String -> a -> b
1090 divZeroError meth v 
1091   = error ("Integral." ++ meth ++ ": divide by 0 (" ++ show v ++ " / 0)")
1092 \end{code}