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