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