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