9fd07c54204a4e42161dc6a22dfb07a8da841f7c
[ghc-hetmet.git] / ghc / lib / exts / Int.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1997-1998
3 %
4
5 \section[Int]{Module @Int@}
6
7 This code is largely copied from the Hugs library of the same name,
8 suitably hammered to use unboxed types.
9
10 \begin{code}
11 -----------------------------------------------------------------------------
12 -- Signed Integers
13 -- Suitable for use with Hugs 1.4 on 32 bit systems.
14 -----------------------------------------------------------------------------
15
16 module Int
17         ( Int8
18         , Int16
19         , Int32
20         , Int64
21         , int8ToInt  -- :: Int8  -> Int
22         , intToInt8  -- :: Int   -> Int8
23         , int16ToInt -- :: Int16 -> Int
24         , intToInt16 -- :: Int   -> Int16
25         , int32ToInt -- :: Int32 -> Int
26         , intToInt32 -- :: Int   -> Int32
27         , intToInt64 -- :: Int   -> Int64
28         -- plus Eq, Ord, Num, Bounded, Real, Integral, Ix, Enum, Read,
29         --  Show and Bits instances for each of Int8, Int16, Int32 and Int64
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 int8ToInt  :: Int8  -> Int
45 intToInt8  :: Int   -> Int8
46 int16ToInt :: Int16 -> Int
47 intToInt16 :: Int   -> Int16
48 int32ToInt :: Int32 -> Int
49 intToInt32 :: Int   -> Int32
50
51 -- And some non-exported ones
52
53 int8ToInt16  :: Int8  -> Int16
54 int8ToInt32  :: Int8  -> Int32
55 int16ToInt8  :: Int16 -> Int8
56 int16ToInt32 :: Int16 -> Int32
57 int32ToInt8  :: Int32 -> Int8
58 int32ToInt16 :: Int32 -> Int16
59
60 int8ToInt16  (I8#  x) = I16# x
61 int8ToInt32  (I8#  x) = I32# x
62 int16ToInt8  (I16# x) = I8#  x
63 int16ToInt32 (I16# x) = I32# x
64 int32ToInt8  (I32# x) = I8#  x
65 int32ToInt16 (I32# x) = I16# x
66 \end{code}
67
68 \subsection[Int8]{The @Int8@ interface}
69
70 \begin{code}
71 data Int8 = I8# Int#
72 instance CCallable Int8
73 instance CReturnable Int8
74
75 int8ToInt (I8# x) = I# (int8ToInt# x)
76 int8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
77    where x' = word2Int# (int2Word# x `and#` int2Word# 0xff#)
78
79 --
80 -- This doesn't perform any bounds checking
81 -- on the value it is passed, nor its sign.
82 -- i.e., show (intToInt8 511) => "-1"
83 --
84 intToInt8 (I# x) = I8# (intToInt8# x)
85 intToInt8# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xff#)
86
87 instance Eq  Int8     where 
88   (I8# x#) == (I8# y#) = x# ==# y#
89   (I8# x#) /= (I8# y#) = x# /=# y#
90
91 instance Ord Int8 where 
92   compare (I8# x#) (I8# y#) = compareInt# (int8ToInt# x#) (int8ToInt# y#)
93
94 compareInt# :: Int# -> Int# -> Ordering
95 compareInt# x# y#
96  | x# <#  y# = LT
97  | x# ==# y# = EQ
98  | otherwise = GT
99
100 instance Num Int8 where
101   (I8# x#) + (I8# y#) = I8# (intToInt8# (x# +# y#))
102   (I8# x#) - (I8# y#) = I8# (intToInt8# (x# -# y#))
103   (I8# x#) * (I8# y#) = I8# (intToInt8# (x# *# y#))
104   negate i@(I8# x#) = 
105      if x# ==# 0#
106       then i
107       else I8# (0x100# -# x#)
108
109   abs           = absReal
110   signum        = signumReal
111   fromInteger (J# a# s# d#)
112                 = case (integer2Int# a# s# d#) of { i# -> I8# (intToInt8# i#) }
113   fromInt       = intToInt8
114
115 instance Bounded Int8 where
116     minBound = 0x80
117     maxBound = 0x7f 
118
119 instance Real Int8 where
120     toRational x = toInteger x % 1
121
122 instance Integral Int8 where
123     div x@(I8# x#) y@(I8# y#) = 
124        if x > 0 && y < 0        then quotInt8 (x-y-1) y
125        else if x < 0 && y > 0   then quotInt8 (x-y+1) y
126        else quotInt8 x y
127     quot x@(I8# _) y@(I8# y#) =
128        if y# /=# 0#
129        then x `quotInt8` y
130        else error "Integral.Int8.quot: divide by 0\n"
131     rem x@(I8# _) y@(I8# y#) =
132        if y# /=# 0#
133        then x `remInt8` y
134        else error "Integral.Int8.rem: divide by 0\n"
135     mod x@(I8# x#) y@(I8# y#) =
136        if x > 0 && y < 0 || x < 0 && y > 0 then
137           if r/=0 then r+y else 0
138        else
139           r
140         where r = remInt8 x y
141     a@(I8# _) `quotRem` b@(I8# _) = (a `quotInt8` b, a `remInt8` b)
142     toInteger i8  = toInteger (int8ToInt i8)
143     toInt     i8  = int8ToInt i8
144
145 remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `remInt#` (int8ToInt# y)))
146 quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `quotInt#` (int8ToInt# y)))
147
148 instance Ix Int8 where
149     range (m,n)          = [m..n]
150     index b@(m,n) i
151               | inRange b i = int8ToInt (i - m)
152               | otherwise   = error (showString "Ix{Int8}.index: Index " .
153                                      showParen True (showsPrec 0 i) .
154                                      showString " out of range " $
155                                      showParen True (showsPrec 0 b) "")
156     inRange (m,n) i      = m <= i && i <= n
157
158 instance Enum Int8 where
159     toEnum         = intToInt8
160     fromEnum       = int8ToInt
161     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int8)]
162     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int8)]
163                           where last = if d < c then minBound else maxBound
164
165 instance Read Int8 where
166     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
167
168 instance Show Int8 where
169     showsPrec p i8 = showsPrec p (int8ToInt i8)
170
171 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
172 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
173
174 instance Bits Int8 where
175   (I8# x) .&. (I8# y) = I8# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
176   (I8# x) .|. (I8# y) = I8# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
177   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
178   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
179   shift (I8# x) i@(I# i#)
180         | i > 0     = I8# (intToInt8# (iShiftL# (int8ToInt# x)  i#))
181         | otherwise = I8# (intToInt8# (iShiftRA# (int8ToInt# x) i#))
182   i8@(I8# x)  `rotate` (I# i)
183         | i ==# 0#    = i8
184         | i ># 0#     = 
185              I8# (intToInt8# ( word2Int#  (
186                      (int2Word# (iShiftL# (int8ToInt# x) i'))
187                              `or#`
188                      (int2Word# (iShiftRA# (word2Int# (
189                                                 (int2Word# x) `and#` 
190                                                 (int2Word# (0x100# -# pow2# i2))))
191                                           i2)))))
192         | otherwise = rotate i8 (I# (8# +# i))
193           where
194            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
195            i2 = 8# -# i'
196   bit i         = shift 1 i
197   setBit x i    = x .|. bit i
198   clearBit x i  = x .&. complement (bit i)
199   complementBit x i = x `xor` bit i
200   testBit x i   = (x .&. bit i) /= 0
201   bitSize  _    = 8
202   isSigned _    = True
203
204 pow2# :: Int# -> Int#
205 pow2# x# = iShiftL# 1# x#
206 \end{code}
207
208 \subsection[Int16]{The @Int16@ interface}
209
210 \begin{code}
211 data Int16  = I16# Int#
212 instance CCallable Int16
213 instance CReturnable Int16
214
215 int16ToInt (I16# x) = I# (int16ToInt# x)
216
217 int16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
218    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
219
220 intToInt16 (I# x) = I16# (intToInt16# x)
221 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
222
223 instance Eq  Int16     where
224   (I16# x#) == (I16# y#) = x# ==# y#
225   (I16# x#) /= (I16# y#) = x# /=# y#
226
227 instance Ord Int16 where
228   compare (I16# x#) (I16# y#) = compareInt# (int16ToInt# x#) (int16ToInt# y#)
229
230 instance Num Int16 where
231   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
232   (I16# x#) - (I16# y#) = I16# (intToInt16# (x# -# y#))
233   (I16# x#) * (I16# y#) = I16# (intToInt16# (x# *# y#))
234   negate i@(I16# x#) = 
235      if x# ==# 0#
236       then i
237       else I16# (0x10000# -# x#)
238   abs           = absReal
239   signum        = signumReal
240   fromInteger (J# a# s# d#)
241                 = case (integer2Int# a# s# d#) of { i# -> I16# (intToInt16# i#) }
242   fromInt       = intToInt16
243
244 instance Bounded Int16 where
245     minBound = 0x8000
246     maxBound = 0x7fff 
247
248 instance Real Int16 where
249     toRational x = toInteger x % 1
250
251 instance Integral Int16 where
252     div x@(I16# x#) y@(I16# y#) = 
253        if x > 0 && y < 0        then quotInt16 (x-y-1) y
254        else if x < 0 && y > 0   then quotInt16 (x-y+1) y
255        else quotInt16 x y
256     quot x@(I16# _) y@(I16# y#) =
257        if y# /=# 0#
258        then x `quotInt16` y
259        else error "Integral.Int16.quot: divide by 0\n"
260     rem x@(I16# _) y@(I16# y#) =
261        if y# /=# 0#
262        then x `remInt16` y
263        else error "Integral.Int16.rem: divide by 0\n"
264     mod x@(I16# x#) y@(I16# y#) =
265        if x > 0 && y < 0 || x < 0 && y > 0 then
266           if r/=0 then r+y else 0
267        else
268           r
269         where r = remInt16 x y
270     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
271     toInteger i16  = toInteger (int16ToInt i16)
272     toInt     i16  = int16ToInt i16
273
274 remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `remInt#` (int16ToInt# y)))
275 quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `quotInt#` (int16ToInt# y)))
276
277 instance Ix Int16 where
278     range (m,n)          = [m..n]
279     index b@(m,n) i
280               | inRange b i = int16ToInt (i - m)
281               | otherwise   = error (showString "Ix{Int16}.index: Index " .
282                                      showParen True (showsPrec 0 i) .
283                                      showString " out of range " $
284                                      showParen True (showsPrec 0 b) "")
285     inRange (m,n) i      = m <= i && i <= n
286
287 instance Enum Int16 where
288     toEnum         = intToInt16
289     fromEnum       = int16ToInt
290     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int16)]
291     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int16)]
292                           where last = if d < c then minBound else maxBound
293
294 instance Read Int16 where
295     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
296
297 instance Show Int16 where
298     showsPrec p i16 = showsPrec p (int16ToInt i16)
299
300 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
301 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
302
303 instance Bits Int16 where
304   (I16# x) .&. (I16# y) = I16# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
305   (I16# x) .|. (I16# y) = I16# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
306   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
307   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
308   shift (I16# x) i@(I# i#)
309         | i > 0     = I16# (intToInt16# (iShiftL# (int16ToInt# x)  i#))
310         | otherwise = I16# (intToInt16# (iShiftRA# (int16ToInt# x) i#))
311   i16@(I16# x)  `rotate` (I# i)
312         | i ==# 0#    = i16
313         | i ># 0#     = 
314              I16# (intToInt16# (word2Int# (
315                     (int2Word# (iShiftL# (int16ToInt# x) i')) 
316                              `or#`
317                     (int2Word# (iShiftRA# ( word2Int# (
318                                     (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
319                                           i2)))))
320         | otherwise = rotate i16 (I# (16# +# i))
321           where
322            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
323            i2 = 16# -# i'
324   bit i             = shift 1 i
325   setBit x i        = x .|. bit i
326   clearBit x i      = x .&. complement (bit i)
327   complementBit x i = x `xor` bit i
328   testBit x i       = (x .&. bit i) /= 0
329   bitSize  _        = 16
330   isSigned _        = True
331 \end{code}
332
333 %
334 %
335 \subsection[Int32]{The @Int32@ interface}
336 %
337 %
338
339 \begin{code}
340 data Int32  = I32# Int#
341 instance CCallable Int32
342 instance CReturnable Int32
343
344 int32ToInt (I32# x) = I# (int32ToInt# x)
345
346 int32ToInt# :: Int# -> Int#
347 #if WORD_SIZE_IN_BYTES > 4
348 int32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
349    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
350 #else
351 int32ToInt# x = x
352 #endif
353
354 intToInt32 (I# x) = I32# (intToInt32# x)
355 intToInt32# :: Int# -> Int#
356 #if WORD_SIZE_IN_BYTES > 4
357 intToInt32# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffffffff#)
358 #else
359 intToInt32# i# = i#
360 #endif
361
362 instance Eq  Int32     where
363   (I32# x#) == (I32# y#) = x# ==# y#
364   (I32# x#) /= (I32# y#) = x# /=# y#
365
366 instance Ord Int32    where
367   compare (I32# x#) (I32# y#) = compareInt# (int32ToInt# x#) (int32ToInt# y#)
368
369 instance Num Int32 where
370   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
371   (I32# x#) - (I32# y#) = I32# (intToInt32# (x# -# y#))
372   (I32# x#) * (I32# y#) = I32# (intToInt32# (x# *# y#))
373 #if WORD_SIZE_IN_BYTES > 4
374   negate i@(I32# x)  = 
375       if x ==# 0#
376        then i
377        else I32# (intToInt32# (0x100000000# -# x'))
378 #else
379   negate (I32# x)  = I32# (negateInt# x)
380 #endif
381   abs           = absReal
382   signum        = signumReal
383   fromInteger (J# a# s# d#)
384                 = case (integer2Int# a# s# d#) of { i# -> I32# (intToInt32# i#) }
385   fromInt       = intToInt32
386
387 -- ToDo: remove LitLit when minBound::Int is fixed (currently it's one
388 -- too high, and doesn't allow the correct minBound to be defined here).
389 instance Bounded Int32 where 
390     minBound = case ``0x80000000'' of { I# x -> I32# x }
391     maxBound = I32# 0x7fffffff#
392
393 instance Real Int32 where
394     toRational x = toInteger x % 1
395
396 instance Integral Int32 where
397     div x@(I32# x#) y@(I32# y#) = 
398        if x > 0 && y < 0        then quotInt32 (x-y-1) y
399        else if x < 0 && y > 0   then quotInt32 (x-y+1) y
400        else quotInt32 x y
401     quot x@(I32# _) y@(I32# y#) =
402        if y# /=# 0#
403        then x `quotInt32` y
404        else error "Integral.Int32.quot: divide by 0\n"
405     rem x@(I32# _) y@(I32# y#) =
406        if y# /=# 0#
407        then x `remInt32` y
408        else error "Integral.Int32.rem: divide by 0\n"
409     mod x@(I32# x#) y@(I32# y#) =
410        if x > 0 && y < 0 || x < 0 && y > 0 then
411           if r/=0 then r+y else 0
412        else
413           r
414         where r = remInt32 x y
415     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
416     toInteger i32  = toInteger (int32ToInt i32)
417     toInt     i32  = int32ToInt i32
418
419 remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `remInt#` (int32ToInt# y)))
420 quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `quotInt#` (int32ToInt# y)))
421
422 instance Ix Int32 where
423     range (m,n)          = [m..n]
424     index b@(m,n) i
425               | inRange b i = int32ToInt (i - m)
426               | otherwise   = error (showString "Ix{Int32}.index: Index " .
427                                      showParen True (showsPrec 0 i) .
428                                      showString " out of range " $
429                                      showParen True (showsPrec 0 b) "")
430     inRange (m,n) i      = m <= i && i <= n
431
432 instance Enum Int32 where
433     toEnum         = intToInt32
434     fromEnum       = int32ToInt
435     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int32)]
436     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int32)]
437                           where last = if d < c then minBound else maxBound
438
439 instance Read Int32 where
440     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
441
442 instance Show Int32 where
443     showsPrec p i32 = showsPrec p (int32ToInt i32)
444
445 instance Bits Int32 where
446   (I32# x) .&. (I32# y)   = I32# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
447   (I32# x) .|. (I32# y)   = I32# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
448   (I32# x) `xor` (I32# y) = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
449 #if WORD_SIZE_IN_BYTES > 4
450   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffffffff#)))
451 #else
452   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
453 #endif
454   shift (I32# x) i@(I# i#)
455         | i > 0     = I32# (intToInt32# (iShiftL# (int32ToInt# x)  i#))
456         | otherwise = I32# (intToInt32# (iShiftRA# (int32ToInt# x) i#))
457   i32@(I32# x)  `rotate` (I# i)
458         | i ==# 0#    = i32
459         | i ># 0#     = 
460              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
461              I32# (intToInt32# ( word2Int# (
462                     (int2Word# (iShiftL# (int32ToInt# x) i')) 
463                           `or#`
464                     (int2Word# (iShiftRA# (word2Int# (
465                                               (int2Word# x) 
466                                                   `and#` 
467                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
468                                           i2)))))
469         | otherwise = rotate i32 (I# (32# +# i))
470           where
471            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
472            i2 = 32# -# i'
473            (I32# maxBound#) = maxBound
474   bit i         = shift 1 i
475   setBit x i    = x .|. bit i
476   clearBit x i  = x .&. complement (bit i)
477   complementBit x i = x `xor` bit i
478   testBit x i   = (x .&. bit i) /= 0
479   bitSize  _    = 32
480   isSigned _    = True
481
482 \end{code}
483
484 \subsection[Int64]{The @Int64@ interface}
485
486 \begin{code}
487 data Int64 = I64 {lo,hi::Int32} deriving (Eq, Ord, Bounded)
488
489 i64ToInteger I64{lo,hi} = toInteger lo + 0x100000000 * toInteger hi 
490 integerToI64 x = case x `quotRem` 0x100000000 of 
491                  (h,l) -> I64{lo=fromInteger l, hi=fromInteger h}
492
493 intToInt64 :: Int -> Int64
494 intToInt64 x =  I64{lo=intToInt32 x, hi=0}
495
496 instance Show Int64 where
497   showsPrec p x = showsPrec p (i64ToInteger x)
498
499 instance Read Int64 where
500   readsPrec p s = [ (integerToI64 x,r) | (x,r) <- readDec s ]
501
502 \end{code}
503
504 %
505 %
506 \subsection[Int Utils]{Miscellaneous utilities}
507 %
508 %
509
510 Code copied from the Prelude
511
512 \begin{code}
513 absReal x    | x >= 0    = x
514              | otherwise = -x
515
516 signumReal x | x == 0    =  0
517              | x > 0     =  1
518              | otherwise = -1
519 \end{code}