[project @ 1998-02-02 16:47:53 by simonm]
[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 module Word
12         ( Word8          -- all abstract.
13         , Word16         -- instances: Eq, Ord
14         , Word32         --  Num, Bounded, Real,
15         , Word64         --  Integral, Ix, Enum,
16                          --  Read, Show, Bits,
17                          --  CCallable, CReturnable
18                          --  (last two 
19
20         , word8ToWord32  -- :: Word8  -> Word32
21         , word32ToWord8  -- :: Word32 -> Word8
22         , word16ToWord32 -- :: Word16 -> Word32
23         , word32ToWord16 -- :: Word32 -> Word16
24         , word8ToInt     -- :: Word8  -> Int
25         , intToWord8     -- :: Int    -> Word8
26         , word16ToInt    -- :: Word16 -> Int
27         , intToWord16    -- :: Int    -> Word16
28         , word32ToInt    -- :: Word32 -> Int
29         , intToWord32    -- :: Int    -> Word32
30         ) where
31
32 import PrelBase
33 import PrelNum
34 import PrelRead
35 import Ix
36 import Bits
37 import PrelGHC
38 import CCall
39
40 -----------------------------------------------------------------------------
41 -- The "official" coercion functions
42 -----------------------------------------------------------------------------
43
44 word8ToWord32  :: Word8  -> Word32
45 word32ToWord8  :: Word32 -> Word8
46 word16ToWord32 :: Word16 -> Word32
47 word32ToWord16 :: Word32 -> Word16
48
49 word8ToInt   :: Word8  -> Int
50 intToWord8   :: Int    -> Word8
51 word16ToInt  :: Word16 -> Int
52 intToWord16  :: Int    -> Word16
53
54 word8ToInt  = word32ToInt    . word8ToWord32
55 intToWord8  = word32ToWord8  . intToWord32
56 word16ToInt = word32ToInt    . word16ToWord32
57 intToWord16 = word32ToWord16 . intToWord32
58
59 intToWord32 (I# x)   = W32# (int2Word# x)
60 word32ToInt (W32# x) = I#   (word2Int# x)
61 \end{code}
62
63 \subsection[Word8]{The @Word8@ interface}
64
65 The byte type @Word8@ is represented in the Haskell
66 heap by boxing up a 32-bit quantity, @Word#@. An invariant
67 for this representation is that the higher 24 bits are
68 *always* zeroed out. A consequence of this is that
69 operations that could possibly overflow have to mask
70 out the top three bytes before building the resulting @Word8@.
71
72 \begin{code}
73 data Word8  = W8# Word#
74
75 instance CCallable Word8
76 instance CReturnable Word8
77
78 word8ToWord32 (W8#  x) = W32# x
79 word32ToWord8 (W32# x) = W8# (wordToWord8# x)
80
81 -- mask out upper three bytes.
82 intToWord8# :: Int# -> Word#
83 intToWord8# i# = (int2Word# i#) `and#` (int2Word# 0xff#)
84
85 wordToWord8# :: Word# -> Word#
86 wordToWord8# w# = w# `and#` (int2Word# 0xff#)
87
88 instance Eq  Word8     where 
89   (W8# x) == (W8# y) = x `eqWord#` y
90   (W8# x) /= (W8# y) = x `neWord#` y
91
92 instance Ord Word8     where 
93   compare (W8# x#) (W8# y#) = compareWord# x# y#
94   (<)  (W8# x) (W8# y)      = x `ltWord#` y
95   (<=) (W8# x) (W8# y)      = x `leWord#` y
96   (>=) (W8# x) (W8# y)      = x `geWord#` y
97   (>)  (W8# x) (W8# y)      = x `gtWord#` y
98   max x@(W8# x#) y@(W8# y#) = 
99      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
100   min x@(W8# x#) y@(W8# y#) =
101      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
102
103 -- Helper function, used by Ord Word* instances.
104 compareWord# :: Word# -> Word# -> Ordering
105 compareWord# x# y# 
106  | x# `ltWord#` y# = LT
107  | x# `eqWord#` y# = EQ
108  | otherwise       = GT
109
110 instance Num Word8 where
111   (W8# x) + (W8# y) = 
112       W8# (intToWord8# (word2Int# x +# word2Int# y))
113   (W8# x) - (W8# y) = 
114       W8# (intToWord8# (word2Int# x -# word2Int# y))
115   (W8# x) * (W8# y) = 
116       W8# (intToWord8# (word2Int# x *# word2Int# y))
117   negate w@(W8# x)  = 
118      if x' ==# 0# 
119       then w
120       else W8# (int2Word# (0x100# -# x'))
121      where
122       x' = word2Int# x
123   abs x         = x
124   signum        = signumReal
125   fromInteger (J# a# s# d#) = W8# (intToWord8# (integer2Int# a# s# d#))
126   fromInt       = intToWord8
127
128 instance Bounded Word8 where
129   minBound = 0
130   maxBound = 0xff
131
132 instance Real Word8 where
133   toRational x = toInteger x % 1
134
135 -- Note: no need to mask results here 
136 -- as they cannot overflow.
137 instance Integral Word8 where
138   div  (W8# x)  (W8# y)   = W8# (x `quotWord#` y)
139   quot (W8# x)  (W8# y)   = W8# (x `quotWord#` y)
140   rem  (W8# x)  (W8# y)   = W8# (x `remWord#` y)
141   mod  (W8# x)  (W8# y)   = W8# (x `remWord#` y)
142   quotRem (W8# x) (W8# y) = (W8# (x `quotWord#` y), W8# (x `remWord#` y))
143   divMod  (W8# x) (W8# y) = (W8# (x `quotWord#` y), W8# (x `remWord#` y))
144   toInteger (W8# x)       = word2Integer# x
145   toInt x                 = word8ToInt x
146
147 instance Ix Word8 where
148     range (m,n)          = [m..n]
149     index b@(m,n) i
150            | inRange b i = word8ToInt (i-m)
151            | otherwise   = error (showString "Ix{Word8}.index: Index " .
152                                   showParen True (showsPrec 0 i) .
153                                   showString " out of range " $
154                                   showParen True (showsPrec 0 b) "")
155     inRange (m,n) i      = m <= i && i <= n
156
157 instance Enum Word8 where
158     toEnum    (I# i)  = W8# (intToWord8# i)
159     fromEnum  (W8# w) = I# (word2Int# w)
160     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Word8)]
161     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Word8)]
162                        where last = if d < c then minBound else maxBound
163
164 instance Read Word8 where
165     readsPrec p = readDec
166
167 instance Show Word8 where
168     showsPrec p = showInt
169
170 --
171 -- Word8s are represented by an (unboxed) 32-bit Word.
172 -- The invariant is that the upper 24 bits are always zeroed out.
173 --
174 instance Bits Word8 where
175   (W8# x)  .&.  (W8# y)    = W8# (x `and#` y)
176   (W8# x)  .|.  (W8# y)    = W8# (x `or#` y)
177   (W8# x) `xor` (W8# y)    = W8# (x `xor#` y)
178   complement (W8# x)       = W8# (x `xor#` int2Word# 0xff#)
179   shift (W8# x#) i@(I# i#)
180         | i > 0     = W8# (wordToWord8# (shiftL# x# i#))
181         | otherwise = W8# (wordToWord8# (shiftRL# x# (negateInt# i#)))
182   w@(W8# x)  `rotate` (I# i)
183         | i ==# 0#    = w
184         | i ># 0#     = W8# ((wordToWord8# (shiftL# x i')) `or#`
185                              (shiftRL# (x `and#` 
186                                         (int2Word# (0x100# -# pow2# i2)))
187                                        i2))
188         | otherwise = rotate w (I# (8# +# i))
189           where
190            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
191            i2 = 8# -# i'
192
193   bit (I# i#)
194         | i# >=# 0# && i# <=# 7# = W8# (wordToWord8# (shiftL# (int2Word# 1#) i#))
195         | otherwise = 0 -- We'll be overbearing, for now..
196
197   setBit x i    = x .|. bit i
198   clearBit x i  = x .&. complement (bit i)
199   complementBit x i = x `xor` bit i
200
201   testBit (W8# x#) (I# i#)
202     | i# <# 8# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
203     | otherwise             = False -- for now, this is really an error.
204
205   bitSize  _    = 8
206   isSigned _    = False
207
208 pow2# :: Int# -> Int#
209 pow2# x# = word2Int# (shiftL# (int2Word# 1#) x#)
210
211 \end{code}
212
213 \subsection[Word16]{The @Word16@ interface}
214
215 The double byte type @Word16@ is represented in the Haskell
216 heap by boxing up a machine word, @Word#@. An invariant
217 for this representation is that only the lower 16 bits are
218 `active', any bits above are {\em always} zeroed out.
219 A consequence of this is that operations that could possibly
220 overflow have to mask out anything above the lower two bytes
221 before putting together the resulting @Word16@.
222
223 \begin{code}
224 data Word16 = W16# Word#
225 instance CCallable Word16
226 instance CReturnable Word16
227
228 word16ToWord32 (W16# x) = W32# x
229 word32ToWord16 (W32# x) = W16# (wordToWord16# x)
230
231 -- mask out upper 16 bits.
232 intToWord16# :: Int# -> Word#
233 intToWord16# i# = ((int2Word# i#) `and#` (int2Word# 0xffff#))
234
235 wordToWord16# :: Word# -> Word#
236 wordToWord16# w# = w# `and#` (int2Word# 0xffff#)
237
238 instance Eq  Word16    where 
239   (W16# x) == (W16# y) = x `eqWord#` y
240   (W16# x) /= (W16# y) = x `neWord#` y
241
242 instance Ord Word16     where
243   compare (W16# x#) (W16# y#) = compareWord# x# y#
244   (<)  (W16# x) (W16# y)      = x `ltWord#` y
245   (<=) (W16# x) (W16# y)      = x `leWord#` y
246   (>=) (W16# x) (W16# y)      = x `geWord#` y
247   (>)  (W16# x) (W16# y)      = x `gtWord#` y
248   max x@(W16# x#) y@(W16# y#) = 
249      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
250   min x@(W16# x#) y@(W16# y#) =
251      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
252
253 instance Num Word16 where
254   (W16# x) + (W16# y) = 
255        W16# (intToWord16# (word2Int# x +# word2Int# y))
256   (W16# x) - (W16# y) = 
257        W16# (intToWord16# (word2Int# x -# word2Int# y))
258   (W16# x) * (W16# y) = 
259        W16# (intToWord16# (word2Int# x *# word2Int# y))
260   negate w@(W16# x)  = 
261        if x' ==# 0# 
262         then w
263         else W16# (int2Word# (0x10000# -# x'))
264        where
265         x' = word2Int# x
266   abs x         = x
267   signum        = signumReal
268   fromInteger (J# a# s# d#) = W16# (intToWord16# (integer2Int# a# s# d#))
269   fromInt       = intToWord16
270
271 instance Bounded Word16 where
272   minBound = 0
273   maxBound = 0xffff
274
275 instance Real Word16 where
276   toRational x = toInteger x % 1
277
278 instance Integral Word16 where
279   div  (W16# x)  (W16# y)   = W16# (x `quotWord#` y)
280   quot (W16# x)  (W16# y)   = W16# (x `quotWord#` y)
281   rem  (W16# x)  (W16# y)   = W16# (x `remWord#` y)
282   mod  (W16# x)  (W16# y)   = W16# (x `remWord#` y)
283   quotRem (W16# x) (W16# y) = (W16# (x `quotWord#` y), W16# (x `remWord#` y))
284   divMod  (W16# x) (W16# y) = (W16# (x `quotWord#` y), W16# (x `remWord#` y))
285   toInteger (W16# x)        = word2Integer# x
286   toInt x                   = word16ToInt x
287
288 instance Ix Word16 where
289   range (m,n)          = [m..n]
290   index b@(m,n) i
291          | inRange b i = word16ToInt (i - m)
292          | otherwise   = error (showString "Ix{Word16}.index: Index " .
293                                 showParen True (showsPrec 0 i) .
294                                 showString " out of range " $
295                                 showParen True (showsPrec 0 b) "")
296   inRange (m,n) i      = m <= i && i <= n
297
298 instance Enum Word16 where
299   toEnum    (I# i)   = W16# (intToWord16# i)
300   fromEnum  (W16# w) = I# (word2Int# w)
301   enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Word16)]
302   enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Word16)]
303                        where last = if d < c then minBound else maxBound
304
305 instance Read Word16 where
306   readsPrec p = readDec
307
308 instance Show Word16 where
309   showsPrec p = showInt
310
311 instance Bits Word16 where
312   (W16# x)  .&.  (W16# y)  = W16# (x `and#` y)
313   (W16# x)  .|.  (W16# y)  = W16# (x `or#` y)
314   (W16# x) `xor` (W16# y)  = W16# (x `xor#` y)
315   complement (W16# x)      = W16# (x `xor#` int2Word# 0xffff#)
316   shift (W16# x#) i@(I# i#)
317         | i > 0     = W16# (wordToWord16# (shiftL# x# i#))
318         | otherwise = W16# (shiftRL# x# (negateInt# i#))
319   w@(W16# x)  `rotate` (I# i)
320         | i ==# 0#    = w
321         | i ># 0#     = W16# ((wordToWord16# (shiftL# x i')) `or#`
322                               (shiftRL# (x `and#` 
323                                          (int2Word# (0x10000# -# pow2# i2)))
324                                         i2))
325         | otherwise = rotate w (I# (16# +# i'))
326           where
327            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
328            i2 = 16# -# i'
329   bit (I# i#)
330         | i# >=# 0# && i# <=# 15# = W16# (shiftL# (int2Word# 1#) i#)
331         | otherwise = 0 -- We'll be overbearing, for now..
332
333   setBit x i    = x .|. bit i
334   clearBit x i  = x .&. complement (bit i)
335   complementBit x i = x `xor` bit i
336
337   testBit (W16# x#) (I# i#)
338     | i# <# 16# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
339     | otherwise             = False -- for now, this is really an error.
340
341   bitSize  _    = 16
342   isSigned _    = False
343
344 \end{code}
345
346 \subsection[Word32]{The @Word32@ interface}
347
348 The quad byte type @Word32@ is represented in the Haskell
349 heap by boxing up a machine word, @Word#@. An invariant
350 for this representation is that any bits above the lower
351 32 are {\em always} zeroed out. A consequence of this is that
352 operations that could possibly overflow have to mask
353 the result before building the resulting @Word16@.
354
355 \begin{code}
356 data Word32 = W32# Word#
357 instance CCallable Word32
358 instance CReturnable Word32
359
360 instance Eq  Word32    where 
361   (W32# x) == (W32# y) = x `eqWord#` y
362   (W32# x) /= (W32# y) = x `neWord#` y
363
364 instance Ord Word32    where
365   compare (W32# x#) (W32# y#) = compareWord# x# y#
366   (<)  (W32# x) (W32# y)      = x `ltWord#` y
367   (<=) (W32# x) (W32# y)      = x `leWord#` y
368   (>=) (W32# x) (W32# y)      = x `geWord#` y
369   (>)  (W32# x) (W32# y)      = x `gtWord#` y
370   max x@(W32# x#) y@(W32# y#) = 
371      case (compareWord# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
372   min x@(W32# x#) y@(W32# y#) =
373      case (compareWord# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
374
375 instance Num Word32 where
376   (W32# x) + (W32# y) = 
377        W32# (intToWord32# (word2Int# x +# word2Int# y))
378   (W32# x) - (W32# y) =
379        W32# (intToWord32# (word2Int# x -# word2Int# y))
380   (W32# x) * (W32# y) = 
381        W32# (intToWord32# (word2Int# x *# word2Int# y))
382 #if WORD_SIZE_IN_BYTES > 4
383   negate w@(W32# x)  = 
384       if x' ==# 0#
385        then w
386        else W32# (intToWord32# (0x100000000# -# x'))
387        where
388         x' = word2Int# x
389 #else
390   negate (W32# x)  = W32# (intToWord32# (negateInt# (word2Int# x)))
391 #endif
392   abs x           = x
393   signum          = signumReal
394   fromInteger (J# a# s# d#) = W32# (intToWord32# (integer2Int# a# s# d#))
395   fromInt (I# x)  = W32# (intToWord32# x)
396     -- ToDo: restrict fromInt{eger} range.
397
398 intToWord32#  :: Int#  -> Word#
399 wordToWord32# :: Word# -> Word#
400
401 #if WORD_SIZE_IN_BYTES > 4
402 intToWord32#  i# = (int2Word# i#) `and#` (int2Word# 0xffffffff)
403 wordToWord32# w# = w# `and#` (int2Word# 0xffffffff)
404 #else
405 intToWord32#  i# = int2Word# i#
406 wordToWord32# w# = w#
407 #endif
408
409 instance Bounded Word32 where
410     minBound = 0
411 #if WORD_SIZE_IN_BYTES > 4
412     maxBound = 0xffffffff
413 #else
414     maxBound = minBound - 1
415 #endif
416
417 instance Real Word32 where
418     toRational x = toInteger x % 1
419
420 instance Integral Word32 where
421     div  x y           =  quotWord32 x y
422     quot x y           =  quotWord32 x y
423     rem  x y           =  remWord32 x y
424     mod  x y           =  remWord32 x y
425     quotRem a b        = (a `quotWord32` b, a `remWord32` b)
426     divMod x y         = quotRem x y
427     toInteger (W32# x) = word2Integer# x
428     toInt     (W32# x) = I# (word2Int# x)
429
430 {-# INLINE quotWord32 #-}
431 {-# INLINE remWord32  #-}
432 (W32# x) `quotWord32` (W32# y) = W32# (x `quotWord#` y)
433 (W32# x) `remWord32`  (W32# y) = W32# (x `remWord#`  y)
434
435 instance Ix Word32 where
436     range (m,n)          = [m..n]
437     index b@(m,n) i
438            | inRange b i = word32ToInt (i - m)
439            | otherwise   = error (showString "Ix{Word32}.index: Index " .
440                                   showParen True (showsPrec 0 i) .
441                                   showString " out of range " $
442                                   showParen True (showsPrec 0 b) "")
443     inRange (m,n) i      = m <= i && i <= n
444
445 instance Enum Word32 where
446     toEnum        = intToWord32
447     fromEnum      = word32ToInt
448     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Word32)]
449     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Word32)]
450                        where last = if d < c then minBound else maxBound
451
452 instance Read Word32 where
453     readsPrec p = readDec
454
455 instance Show Word32 where
456     showsPrec p = showInt
457
458 instance Bits Word32 where
459   (W32# x)  .&.  (W32# y)  = W32# (x `and#` y)
460   (W32# x)  .|.  (W32# y)  = W32# (x `or#` y)
461   (W32# x) `xor` (W32# y)  = W32# (x `xor#` y)
462   complement (W32# x)      = W32# (x `xor#` mb#) where (W32# mb#) = maxBound
463   shift (W32# x) i@(I# i#)
464         | i > 0     = W32# (wordToWord32# (shiftL# x i#))
465         | otherwise = W32# (shiftRL# x (negateInt# i#))
466   w@(W32# x)  `rotate` (I# i)
467         | i ==# 0#    = w
468         | i ># 0#     = W32# ((wordToWord32# (shiftL# x i')) `or#`
469                               (shiftRL# (x `and#` 
470                                         (int2Word# (word2Int# maxBound# -# pow2# i2 +# 1#)))
471                                      i2))
472         | otherwise = rotate w (I# (32# +# i))
473           where
474            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
475            i2 = 32# -# i'
476            (W32# maxBound#) = maxBound
477
478   bit (I# i#)
479         | i# >=# 0# && i# <=# 31# = W32# (shiftL# (int2Word# 1#) i#)
480         | otherwise = 0 -- We'll be overbearing, for now..
481
482   setBit x i        = x .|. bit i
483   clearBit x i      = x .&. complement (bit i)
484   complementBit x i = x `xor` bit i
485
486   testBit (W32# x#) (I# i#)
487     | i# <# 32# && i# >=# 0# = (word2Int# (x# `and#` (shiftL# (int2Word# 1#) i#))) /=# 0#
488     | otherwise             = False -- for now, this is really an error.
489   bitSize  _        = 32
490   isSigned _        = False
491
492 \end{code}
493
494 \subsection[Word64]{The @Word64@ interface}
495
496 \begin{code}
497 data Word64 = W64 {lo,hi::Word32} deriving (Eq, Ord, Bounded)
498
499 w64ToInteger W64{lo,hi} = toInteger lo + 0x100000000 * toInteger hi 
500 integerToW64 x = case x `quotRem` 0x100000000 of 
501                  (h,l) -> W64{lo=fromInteger l, hi=fromInteger h}
502
503 instance Show Word64 where
504   showsPrec p x = showsPrec p (w64ToInteger x)
505
506 instance Read Word64 where
507   readsPrec p s = [ (integerToW64 x,r) | (x,r) <- readDec s ]
508
509 -----------------------------------------------------------------------------
510 -- End of exported definitions
511 --
512 -- The remainder of this file consists of definitions which are only
513 -- used in the implementation.
514 -----------------------------------------------------------------------------
515
516 -----------------------------------------------------------------------------
517 -- Code copied from the Prelude
518 -----------------------------------------------------------------------------
519
520 signumReal x | x == 0    =  0
521              | x > 0     =  1
522              | otherwise = -1
523
524 -- showInt is used for positive numbers only
525 -- stolen from Hugs prelude --SDM
526 showInt    :: Integral a => a -> ShowS
527 showInt n r | n < 0 = error "Word.showInt: can't show negative numbers"
528             | otherwise =
529               let (n',d) = quotRem n 10
530                   r'     = toEnum (fromEnum '0' + fromIntegral d) : r
531               in  if n' == 0 then r' else showInt n' r'
532
533 \end{code}