791a41c9d54306480e56067e480671db163035e0
[ghc-hetmet.git] / ghc / lib / std / PrelInt.lhs
1 %
2 % (c) The University of Glasgow, 2000
3 %
4 \section[PrelInt]{Module @PrelInt@}
5
6 \begin{code}
7 {-# OPTIONS -monly-3-regs #-}
8
9 module PrelInt 
10    ( 
11         Int8(..), Int16(..), Int32(..), Int64(..)
12
13         , intToInt8      -- :: Int     -> Int8
14         , intToInt16     -- :: Int     -> Int16
15         , intToInt32     -- :: Int     -> Int32
16         , intToInt64     -- :: Int     -> Int64
17
18         , integerToInt8  -- :: Integer -> Int8
19         , integerToInt16 -- :: Integer -> Int16
20         , integerToInt32 -- :: Integer -> Int32
21         , integerToInt64 -- :: Integer -> Int64
22
23         , int8ToInt      -- :: Int8    -> Int
24         , int8ToInteger  -- :: Int8    -> Integer
25         , int8ToInt16    -- :: Int8    -> Int16
26         , int8ToInt32    -- :: Int8    -> Int32
27         , int8ToInt64    -- :: Int8    -> Int64
28
29         , int16ToInt     -- :: Int16   -> Int
30         , int16ToInteger -- :: Int16   -> Integer
31         , int16ToInt8    -- :: Int16   -> Int8
32         , int16ToInt32   -- :: Int16   -> Int32
33         , int16ToInt64   -- :: Int16   -> Int64
34
35         , int32ToInt     -- :: Int32   -> Int
36         , int32ToInteger -- :: Int32   -> Integer
37         , int32ToInt8    -- :: Int32   -> Int8
38         , int32ToInt16   -- :: Int32   -> Int16
39         , int32ToInt64   -- :: Int32   -> Int64
40
41         , int64ToInt     -- :: Int64   -> Int
42         , int64ToInteger -- :: Int64   -> Integer
43         , int64ToInt8    -- :: Int64   -> Int8
44         , int64ToInt16   -- :: Int64   -> Int16
45         , int64ToInt32   -- :: Int64   -> Int32
46
47         -- internal stuff
48         , intToInt8#, i8ToInt#, intToInt16#, i16ToInt#, intToInt32#, i32ToInt#,
49         , intToInt64#, plusInt64#, minusInt64#, negateInt64#
50
51  ) where
52
53 import PrelWord
54 import PrelBits
55 import PrelArr
56 import PrelRead
57 import PrelReal
58 import PrelNum
59 import PrelBase
60
61 -- ---------------------------------------------------------------------------
62 -- Coercion functions (DEPRECATED)
63 -- ---------------------------------------------------------------------------
64
65 intToInt8      :: Int     -> Int8
66 intToInt16     :: Int     -> Int16
67 intToInt32     :: Int     -> Int32
68 intToInt64     :: Int     -> Int64
69
70 integerToInt8  :: Integer -> Int8
71 integerToInt16 :: Integer -> Int16
72 integerToInt32 :: Integer -> Int32
73 integerToInt64 :: Integer -> Int64
74
75 int8ToInt      :: Int8    -> Int
76 int8ToInteger  :: Int8    -> Integer
77 int8ToInt16    :: Int8    -> Int16
78 int8ToInt32    :: Int8    -> Int32
79 int8ToInt64    :: Int8    -> Int64
80
81 int16ToInt     :: Int16   -> Int
82 int16ToInteger :: Int16   -> Integer
83 int16ToInt8    :: Int16   -> Int8
84 int16ToInt32   :: Int16   -> Int32
85 int16ToInt64   :: Int16   -> Int64
86
87 int32ToInt     :: Int32   -> Int
88 int32ToInteger :: Int32   -> Integer
89 int32ToInt8    :: Int32   -> Int8
90 int32ToInt16   :: Int32   -> Int16
91 int32ToInt64   :: Int32   -> Int64
92
93 int64ToInt     :: Int64   -> Int
94 int64ToInteger :: Int64   -> Integer
95 int64ToInt8    :: Int64   -> Int8
96 int64ToInt16   :: Int64   -> Int16
97 int64ToInt32   :: Int64   -> Int32
98
99 integerToInt8  = fromInteger
100 integerToInt16 = fromInteger
101 integerToInt32 = fromInteger
102
103 int8ToInt16    = intToInt16 . int8ToInt
104 int8ToInt32    = intToInt32 . int8ToInt
105 int16ToInt32   = intToInt32 . int16ToInt
106
107 int16ToInt8  (I16# x) = I8#  (intToInt8# x)
108 int32ToInt8  (I32# x) = I8#  (intToInt8# x)
109 int32ToInt16 (I32# x) = I16# (intToInt16# x)
110
111 int8ToInteger  = toInteger
112 int8ToInt64    = int32ToInt64 . int8ToInt32
113
114 int16ToInteger = toInteger
115 int16ToInt64   = int32ToInt64 . int16ToInt32
116
117 int32ToInteger = toInteger
118
119 int64ToInt8    = int32ToInt8  . int64ToInt32
120 int64ToInt16   = int32ToInt16 . int64ToInt32
121
122 -----------------------------------------------------------------------------
123 -- The following rules for fromIntegral remove the need to export specialized
124 -- conversion functions.
125 -----------------------------------------------------------------------------
126
127 {-# RULES
128    "fromIntegral/Int->Int8"         fromIntegral = intToInt8;
129    "fromIntegral/Int->Int16"        fromIntegral = intToInt16;
130    "fromIntegral/Int->Int32"        fromIntegral = intToInt32;
131    "fromIntegral/Int->Int64"        fromIntegral = intToInt64;
132
133    "fromIntegral/Integer->Int8"     fromIntegral = integerToInt8;
134    "fromIntegral/Integer->Int16"    fromIntegral = integerToInt16;
135    "fromIntegral/Integer->Int32"    fromIntegral = integerToInt32;
136    "fromIntegral/Integer->Int64"    fromIntegral = integerToInt64;
137
138    "fromIntegral/Int8->Int"         fromIntegral = int8ToInt;
139    "fromIntegral/Int8->Integer"     fromIntegral = int8ToInteger;
140    "fromIntegral/Int8->Int16"       fromIntegral = int8ToInt16;
141    "fromIntegral/Int8->Int32"       fromIntegral = int8ToInt32;
142    "fromIntegral/Int8->Int64"       fromIntegral = int8ToInt64;
143
144    "fromIntegral/Int16->Int"        fromIntegral = int16ToInt;
145    "fromIntegral/Int16->Integer"    fromIntegral = int16ToInteger;
146    "fromIntegral/Int16->Int8"       fromIntegral = int16ToInt8;
147    "fromIntegral/Int16->Int32"      fromIntegral = int16ToInt32;
148    "fromIntegral/Int16->Int64"      fromIntegral = int16ToInt64;
149
150    "fromIntegral/Int32->Int"        fromIntegral = int32ToInt;
151    "fromIntegral/Int32->Integer"    fromIntegral = int32ToInteger;
152    "fromIntegral/Int32->Int8"       fromIntegral = int32ToInt8;
153    "fromIntegral/Int32->Int16"      fromIntegral = int32ToInt16;
154    "fromIntegral/Int32->Int64"      fromIntegral = int32ToInt64;
155
156    "fromIntegral/Int64->Int"        fromIntegral = int64ToInt;
157    "fromIntegral/Int64->Integer"    fromIntegral = int64ToInteger;
158    "fromIntegral/Int64->Int8"       fromIntegral = int64ToInt8;
159    "fromIntegral/Int64->Int16"      fromIntegral = int64ToInt16;
160    "fromIntegral/Int64->Int32"      fromIntegral = int64ToInt32
161  #-}
162
163 -- -----------------------------------------------------------------------------
164 -- Int8
165 -- -----------------------------------------------------------------------------
166
167 data Int8 = I8# Int#
168
169 instance CCallable Int8
170 instance CReturnable Int8
171
172 int8ToInt (I8# x)  = I# (i8ToInt# x)
173
174 i8ToInt# :: Int# -> Int#
175 i8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
176    where x' = word2Int# (int2Word# x `and#` int2Word# 0xff#)
177
178 -- This doesn't perform any bounds checking on the value it is passed,
179 -- nor its sign, i.e., show (intToInt8 511) => "-1"
180 intToInt8 (I# x) = I8# (intToInt8# x)
181
182 intToInt8# :: Int# -> Int#
183 intToInt8# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xff#)
184
185 instance Eq  Int8     where 
186   (I8# x#) == (I8# y#) = x# ==# y#
187   (I8# x#) /= (I8# y#) = x# /=# y#
188
189 instance Ord Int8 where 
190   compare (I8# x#) (I8# y#) = compareInt# (i8ToInt# x#) (i8ToInt# y#)
191
192 compareInt# :: Int# -> Int# -> Ordering
193 compareInt# x# y#
194  | x# <#  y# = LT
195  | x# ==# y# = EQ
196  | otherwise = GT
197
198 instance Num Int8 where
199   (I8# x#) + (I8# y#) = I8# (intToInt8# (x# +# y#))
200   (I8# x#) - (I8# y#) = I8# (intToInt8# (x# -# y#))
201   (I8# x#) * (I8# y#) = I8# (intToInt8# (x# *# y#))
202   negate i@(I8# x#) = 
203      if x# ==# 0#
204       then i
205       else I8# (0x100# -# x#)
206
207   abs           = absReal
208   signum        = signumReal
209   fromInteger (S# i#)    = I8# (intToInt8# i#)
210   fromInteger (J# s# d#) = I8# (intToInt8# (integer2Int# s# d#))
211
212 instance Bounded Int8 where
213     minBound = 0x80
214     maxBound = 0x7f 
215
216 instance Real Int8 where
217     toRational x = toInteger x % 1
218
219 instance Integral Int8 where
220     div x y
221        | x > 0 && y < 0 = quotInt8 (x-y-1) y
222        | x < 0 && y > 0 = quotInt8 (x-y+1) y
223        | otherwise      = quotInt8 x y
224     quot x@(I8# _) y@(I8# y#)
225        | y# /=# 0# = x `quotInt8` y
226        | otherwise = divZeroError "quot{Int8}" x
227     rem x@(I8# _) y@(I8# y#)
228        | y# /=# 0#  = x `remInt8` y
229        | otherwise  = divZeroError "rem{Int8}" x
230     mod x y
231        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
232        | otherwise = r
233         where r = remInt8 x y
234
235     a@(I8# _) `quotRem` b@(I8# _) = (a `quotInt8` b, a `remInt8` b)
236     toInteger i8  = toInteger (int8ToInt i8)
237     toInt     i8  = int8ToInt i8
238
239
240 remInt8, quotInt8 :: Int8 -> Int8 -> Int8
241 remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `remInt#`  (i8ToInt# y)))
242 quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `quotInt#` (i8ToInt# y)))
243
244 instance Ix Int8 where
245     range (m,n)          = [m..n]
246     index b@(m,_) i
247               | inRange b i = int8ToInt (i - m)
248               | otherwise   = indexError b i "Int8"
249     inRange (m,n) i      = m <= i && i <= n
250
251 instance Enum Int8 where
252     succ i
253       | i == maxBound = succError "Int8"
254       | otherwise     = i+1
255     pred i
256       | i == minBound = predError "Int8"
257       | otherwise     = i-1
258
259     toEnum x
260       | x >= toInt (minBound::Int8) && x <= toInt (maxBound::Int8) 
261       = intToInt8 x
262       | otherwise
263       = toEnumError "Int8" x (minBound::Int8,maxBound::Int8)
264
265     fromEnum           = int8ToInt
266     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int8)]
267     enumFromThen e1 e2 = 
268              map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int8)]
269                 where 
270                    last 
271                      | e2 < e1   = minBound
272                      | otherwise = maxBound
273
274 instance Read Int8 where
275     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
276
277 instance Show Int8 where
278     showsPrec p i8 = showsPrec p (int8ToInt i8)
279
280 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
281 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
282
283 instance Bits Int8 where
284   (I8# x) .&. (I8# y) = I8# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
285   (I8# x) .|. (I8# y) = I8# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
286   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
287   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
288   shift (I8# x) i@(I# i#)
289         | i > 0     = I8# (intToInt8# (iShiftL# (i8ToInt# x)  i#))
290         | otherwise = I8# (intToInt8# (iShiftRA# (i8ToInt# x) (negateInt# i#)))
291   i8@(I8# x)  `rotate` (I# i)
292         | i ==# 0#    = i8
293         | i ># 0#     = 
294              I8# (intToInt8# ( word2Int#  (
295                      (int2Word# (iShiftL# (i8ToInt# x) i'))
296                              `or#`
297                      (int2Word# (iShiftRA# (word2Int# (
298                                                 (int2Word# x) `and#` 
299                                                 (int2Word# (0x100# -# pow2# i2))))
300                                           i2)))))
301         | otherwise = rotate i8 (I# (8# +# i))
302           where
303            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
304            i2 = 8# -# i'
305   bitSize  _    = 8
306   isSigned _    = True
307
308 pow2# :: Int# -> Int#
309 pow2# x# = iShiftL# 1# x#
310
311 pow2_64# :: Int# -> Int64#
312 pow2_64# x# = word64ToInt64# (shiftL64# (wordToWord64# (int2Word# 1#)) x#)
313
314 -- -----------------------------------------------------------------------------
315 -- Int16
316 -- -----------------------------------------------------------------------------
317
318 data Int16  = I16# Int#
319
320 instance CCallable Int16
321 instance CReturnable Int16
322
323 int16ToInt  (I16# x) = I# (i16ToInt# x)
324
325 i16ToInt# :: Int# -> Int#
326 i16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
327    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
328
329 -- This doesn't perform any bounds checking on the value it is passed,
330 -- nor its sign, i.e., show (intToInt8 131071) => "-1"
331 intToInt16 (I# x) = I16# (intToInt16# x)
332
333 intToInt16# :: Int# -> Int#
334 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
335
336 instance Eq  Int16     where
337   (I16# x#) == (I16# y#) = x# ==# y#
338   (I16# x#) /= (I16# y#) = x# /=# y#
339
340 instance Ord Int16 where
341   compare (I16# x#) (I16# y#) = compareInt# (i16ToInt# x#) (i16ToInt# y#)
342
343 instance Num Int16 where
344   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
345   (I16# x#) - (I16# y#) = I16# (intToInt16# (x# -# y#))
346   (I16# x#) * (I16# y#) = I16# (intToInt16# (x# *# y#))
347   negate i@(I16# x#) = 
348      if x# ==# 0#
349       then i
350       else I16# (0x10000# -# x#)
351   abs           = absReal
352   signum        = signumReal
353   fromInteger (S# i#)    = I16# (intToInt16# i#)
354   fromInteger (J# s# d#) = I16# (intToInt16# (integer2Int# s# d#))
355
356 instance Bounded Int16 where
357     minBound = 0x8000
358     maxBound = 0x7fff 
359
360 instance Real Int16 where
361     toRational x = toInteger x % 1
362
363 instance Integral Int16 where
364     div x y
365        | x > 0 && y < 0 = quotInt16 (x-y-1) y
366        | x < 0 && y > 0 = quotInt16 (x-y+1) y
367        | otherwise      = quotInt16 x y
368     quot x@(I16# _) y@(I16# y#)
369        | y# /=# 0#      = x `quotInt16` y
370        | otherwise      = divZeroError "quot{Int16}" x
371     rem x@(I16# _) y@(I16# y#)
372        | y# /=# 0#      = x `remInt16` y
373        | otherwise      = divZeroError "rem{Int16}" x
374     mod x y
375        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
376        | otherwise                        = r
377         where r = remInt16 x y
378
379     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
380     toInteger i16  = toInteger (int16ToInt i16)
381     toInt     i16  = int16ToInt i16
382
383 remInt16, quotInt16 :: Int16 -> Int16 -> Int16
384 remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `remInt#` (i16ToInt# y)))
385 quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `quotInt#` (i16ToInt# y)))
386
387 instance Ix Int16 where
388     range (m,n)          = [m..n]
389     index b@(m,_) i
390               | inRange b i = int16ToInt (i - m)
391               | otherwise   = indexError b i "Int16"
392     inRange (m,n) i      = m <= i && i <= n
393
394 instance Enum Int16 where
395     succ i
396       | i == maxBound = succError "Int16"
397       | otherwise     = i+1
398
399     pred i
400       | i == minBound = predError "Int16"
401       | otherwise     = i-1
402
403     toEnum x
404       | x >= toInt (minBound::Int16) && x <= toInt (maxBound::Int16) 
405       = intToInt16 x
406       | otherwise
407       = toEnumError "Int16" x (minBound::Int16, maxBound::Int16)
408
409     fromEnum         = int16ToInt
410
411     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int16)]
412     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int16)]
413                           where last 
414                                   | e2 < e1   = minBound
415                                   | otherwise = maxBound
416
417 instance Read Int16 where
418     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
419
420 instance Show Int16 where
421     showsPrec p i16 = showsPrec p (int16ToInt i16)
422
423
424 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
425 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
426
427 instance Bits Int16 where
428   (I16# x) .&. (I16# y) = I16# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
429   (I16# x) .|. (I16# y) = I16# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
430   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
431   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
432   shift (I16# x) i@(I# i#)
433         | i > 0     = I16# (intToInt16# (iShiftL# (i16ToInt# x)  i#))
434         | otherwise = I16# (intToInt16# (iShiftRA# (i16ToInt# x) (negateInt# i#)))
435   i16@(I16# x)  `rotate` (I# i)
436         | i ==# 0#    = i16
437         | i ># 0#     = 
438              I16# (intToInt16# (word2Int# (
439                     (int2Word# (iShiftL# (i16ToInt# x) i')) 
440                              `or#`
441                     (int2Word# (iShiftRA# ( word2Int# (
442                                     (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
443                                           i2)))))
444         | otherwise = rotate i16 (I# (16# +# i))
445           where
446            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
447            i2 = 16# -# i'
448   bitSize  _        = 16
449   isSigned _        = True
450
451 -- -----------------------------------------------------------------------------
452 -- Int32
453 -- -----------------------------------------------------------------------------
454
455 data Int32  = I32# Int#
456
457 instance CCallable Int32
458 instance CReturnable Int32
459
460 int32ToInt  (I32# x) = I# (i32ToInt# x)
461
462 i32ToInt# :: Int# -> Int#
463 #if WORD_SIZE_IN_BYTES > 4
464 i32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
465    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
466 #else
467 i32ToInt# x = x
468 #endif
469
470 intToInt32 (I# x) = I32# (intToInt32# x)
471
472 intToInt32# :: Int# -> Int#
473 #if WORD_SIZE_IN_BYTES > 4
474 intToInt32# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffffffff#)
475 #else
476 intToInt32# i# = i#
477 #endif
478
479 instance Eq  Int32     where
480   (I32# x#) == (I32# y#) = x# ==# y#
481   (I32# x#) /= (I32# y#) = x# /=# y#
482
483 instance Ord Int32    where
484   compare (I32# x#) (I32# y#) = compareInt# (i32ToInt# x#) (i32ToInt# y#)
485
486 instance Num Int32 where
487   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
488   (I32# x#) - (I32# y#) = I32# (intToInt32# (x# -# y#))
489   (I32# x#) * (I32# y#) = I32# (intToInt32# (x# *# y#))
490 #if WORD_SIZE_IN_BYTES > 4
491   negate i@(I32# x)  = 
492       if x ==# 0#
493        then i
494        else I32# (intToInt32# (0x100000000# -# x'))
495 #else
496   negate (I32# x)  = I32# (negateInt# x)
497 #endif
498   abs           = absReal
499   signum        = signumReal
500   fromInteger (S# i#)    = I32# (intToInt32# i#)
501   fromInteger (J# s# d#) = I32# (intToInt32# (integer2Int# s# d#))
502
503
504 instance Bounded Int32 where 
505     minBound = int2Int32 minBound
506     maxBound = int2Int32 maxBound
507
508 int2Int32 :: Int -> Int32
509 int2Int32 (I# i#) = I32# (intToInt32# i#)
510
511 instance Real Int32 where
512     toRational x = toInteger x % 1
513
514 instance Integral Int32 where
515     div x y
516        | x > 0 && y < 0 = quotInt32 (x-y-1) y
517        | x < 0 && y > 0 = quotInt32 (x-y+1) y
518        | otherwise      = quotInt32 x y
519     quot x@(I32# _) y@(I32# y#)
520        | y# /=# 0#  = x `quotInt32` y
521        | otherwise  = divZeroError "quot{Int32}" x
522     rem x@(I32# _) y@(I32# y#)
523        | y# /=# 0#  = x `remInt32` y
524        | otherwise  = divZeroError "rem{Int32}" x
525     mod x y
526        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
527        | otherwise                        = r
528         where r = remInt32 x y
529
530     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
531     toInteger i32  = toInteger (int32ToInt i32)
532     toInt     i32  = int32ToInt i32
533
534 remInt32, quotInt32 :: Int32 -> Int32 -> Int32
535 remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `remInt#`  (i32ToInt# y)))
536 quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `quotInt#` (i32ToInt# y)))
537
538 instance Ix Int32 where
539     range (m,n)          = [m..n]
540     index b@(m,_) i
541               | inRange b i = int32ToInt (i - m)
542               | otherwise   = indexError b i "Int32"
543     inRange (m,n) i      = m <= i && i <= n
544
545 instance Enum Int32 where
546     succ i
547       | i == maxBound = succError "Int32"
548       | otherwise     = i+1
549
550     pred i
551       | i == minBound = predError "Int32"
552       | otherwise     = i-1
553
554     toEnum x
555         -- with Int having the same range as Int32, the following test
556         -- shouldn't fail. However, having it here 
557       | x >= toInt (minBound::Int32) && x <= toInt (maxBound::Int32) 
558       = intToInt32 x
559       | otherwise
560       = toEnumError "Int32" x (minBound::Int32, maxBound::Int32)
561
562     fromEnum           = int32ToInt
563
564     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int32)]
565     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int32)]
566                           where 
567                             last
568                              | e2 < e1   = minBound
569                              | otherwise = maxBound
570
571
572 instance Read Int32 where
573     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
574
575 instance Show Int32 where
576     showsPrec p i32 = showsPrec p (int32ToInt i32)
577
578 instance Bits Int32 where
579   (I32# x) .&. (I32# y)   = I32# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
580   (I32# x) .|. (I32# y)   = I32# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
581   (I32# x) `xor` (I32# y) = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
582 #if WORD_SIZE_IN_BYTES > 4
583   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffffffff#)))
584 #else
585   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
586 #endif
587   shift (I32# x) i@(I# i#)
588         | i > 0     = I32# (intToInt32# (iShiftL# (i32ToInt# x)  i#))
589         | otherwise = I32# (intToInt32# (iShiftRA# (i32ToInt# x) (negateInt# i#)))
590   i32@(I32# x)  `rotate` (I# i)
591         | i ==# 0#    = i32
592         | i ># 0#     = 
593              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
594              I32# (intToInt32# ( word2Int# (
595                     (int2Word# (iShiftL# (i32ToInt# x) i')) 
596                           `or#`
597                     (int2Word# (iShiftRA# (word2Int# (
598                                               (int2Word# x) 
599                                                   `and#` 
600                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
601                                           i2)))))
602         | otherwise = rotate i32 (I# (32# +# i))
603           where
604            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
605            i2 = 32# -# i'
606            (I32# maxBound#) = maxBound
607   bitSize  _    = 32
608   isSigned _    = True
609
610 -- -----------------------------------------------------------------------------
611 -- Int64
612 -- -----------------------------------------------------------------------------
613
614 #if WORD_SIZE_IN_BYTES == 8
615 data Int64  = I64# Int#
616
617 int32ToInt64 (I32# i#) = I64# i#
618
619 intToInt32# :: Int# -> Int#
620 intToInt32# i# = word2Int# ((int2Word# i#) `and#` (case (maxBound::Word32) of W# x# -> x#))
621
622 int64ToInt32 (I64# i#) = I32# (intToInt32# w#)
623
624 instance Eq  Int64     where 
625   (I64# x) == (I64# y) = x `eqInt#` y
626   (I64# x) /= (I64# y) = x `neInt#` y
627
628 instance Ord Int32    where
629   compare (I64# x#) (I64# y#) = compareInt# x# y#
630
631 instance Num Int64 where
632   (I64# x) + (I64# y) = I64# (x +# y)
633   (I64# x) - (I64# y) = I64# (x -# y)
634   (I64# x) * (I64# y) = I64# (x *# y)
635   negate w@(I64# x)   = I64# (negateInt# x)
636   abs x               = absReal
637   signum              = signumReal
638   fromInteger (S# i#)    = I64# i#
639   fromInteger (J# s# d#) = I64# (integer2Int# s# d#)
640
641 instance Bounded Int64 where
642   minBound = integerToInt64 (-0x8000000000000000)
643   maxBound = integerToInt64 0x7fffffffffffffff
644
645 instance Integral Int64 where
646     div x y
647       | x > 0 && y < 0  = quotInt64 (x-y-1) y
648       | x < 0 && y > 0  = quotInt64 (x-y+1) y
649       | otherwise       = quotInt64 x y
650
651     quot x@(I64# _) y@(I64# y#)
652        | y# /=# 0# = x `quotInt64` y
653        | otherwise = divZeroError "quot{Int64}" x
654
655     rem x@(I64# _) y@(I64# y#)
656        | y# /=# 0# = x `remInt64` y
657        | otherwise = divZeroError "rem{Int64}" x
658
659     mod x y
660        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
661        | otherwise = r
662         where r = remInt64 x y
663
664     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
665     toInteger (I64# i#) = toInteger (I# i#)
666     toInt     (I64# i#) = I# i#
667
668 remInt64  (I64# x) (I64# y) = I64# (x `remInt#` y)
669 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt#` y)
670
671 int64ToInteger (I64# i#) = toInteger (I# i#)
672 integerToInt64 i = case fromInteger i of { I# i# -> I64# i# }
673
674 intToInt64 (I# i#) = I64# i#
675 int64ToInt (I64# i#) = I# i#
676
677 #else
678 --assume: support for long-longs
679 data Int64 = I64# Int64#
680
681 int32ToInt64 (I32# i#) = I64# (intToInt64# i#)
682 int64ToInt32 (I64# i#) = I32# (int64ToInt# i#)
683
684 int64ToInteger (I64# x#) = 
685    case int64ToInteger# x# of
686      (# s#, p# #) -> J# s# p#
687
688 integerToInt64 (S# i#) = I64# (intToInt64# i#)
689 integerToInt64 (J# s# d#) = I64# (integerToInt64# s# d#)
690
691 instance Eq  Int64     where 
692   (I64# x) == (I64# y) = x `eqInt64#` y
693   (I64# x) /= (I64# y) = x `neInt64#` y
694
695 instance Ord Int64     where 
696   compare (I64# x) (I64# y)   = compareInt64# x y
697   (<)  (I64# x) (I64# y)      = x `ltInt64#` y
698   (<=) (I64# x) (I64# y)      = x `leInt64#` y
699   (>=) (I64# x) (I64# y)      = x `geInt64#` y
700   (>)  (I64# x) (I64# y)      = x `gtInt64#` y
701   max x@(I64# x#) y@(I64# y#) = 
702      case (compareInt64# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
703   min x@(I64# x#) y@(I64# y#) =
704      case (compareInt64# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
705
706 instance Num Int64 where
707   (I64# x) + (I64# y) = I64# (x `plusInt64#`  y)
708   (I64# x) - (I64# y) = I64# (x `minusInt64#` y)
709   (I64# x) * (I64# y) = I64# (x `timesInt64#` y)
710   negate (I64# x)     = I64# (negateInt64# x)
711   abs x               = absReal x
712   signum              = signumReal
713   fromInteger i       = integerToInt64 i
714
715 compareInt64# :: Int64# -> Int64# -> Ordering
716 compareInt64# i# j# 
717  | i# `ltInt64#` j# = LT
718  | i# `eqInt64#` j# = EQ
719  | otherwise        = GT
720
721 instance Bounded Int64 where
722   minBound = integerToInt64 (-0x8000000000000000)
723   maxBound = integerToInt64 0x7fffffffffffffff
724
725 instance Integral Int64 where
726     div x y
727       | x > 0 && y < 0  = quotInt64 (x-y-1) y
728       | x < 0 && y > 0  = quotInt64 (x-y+1) y
729       | otherwise       = quotInt64 x y
730
731     quot x@(I64# _) y@(I64# y#)
732        | y# `neInt64#` (intToInt64# 0#) = x `quotInt64` y
733        | otherwise = divZeroError "quot{Int64}" x
734
735     rem x@(I64# _) y@(I64# y#)
736        | y# `neInt64#` (intToInt64# 0#) = x `remInt64` y
737        | otherwise = divZeroError "rem{Int64}" x
738
739     mod x y
740        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
741        | otherwise = r
742         where r = remInt64 x y
743
744     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
745     toInteger i         = int64ToInteger i
746     toInt     i         = int64ToInt i
747
748 remInt64, quotInt64 :: Int64 -> Int64 -> Int64
749 remInt64  (I64# x) (I64# y) = I64# (x `remInt64#` y)
750 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt64#` y)
751
752 intToInt64 (I# i#) = I64# (intToInt64# i#)
753 int64ToInt (I64# i#) = I# (int64ToInt# i#)
754
755 -- Int64# primop wrappers:
756
757 ltInt64# :: Int64# -> Int64# -> Bool
758 ltInt64# x# y# = stg_ltInt64 x# y# /=# 0#
759       
760 leInt64# :: Int64# -> Int64# -> Bool
761 leInt64# x# y# = stg_leInt64 x# y# /=# 0#
762
763 eqInt64# :: Int64# -> Int64# -> Bool
764 eqInt64# x# y# = stg_eqInt64 x# y# /=# 0#
765
766 neInt64# :: Int64# -> Int64# -> Bool
767 neInt64# x# y# = stg_neInt64 x# y# /=# 0#
768
769 geInt64# :: Int64# -> Int64# -> Bool
770 geInt64# x# y# = stg_geInt64 x# y# /=# 0#
771
772 gtInt64# :: Int64# -> Int64# -> Bool
773 gtInt64# x# y# = stg_gtInt64 x# y# /=# 0#
774
775 foreign import "stg_intToInt64" unsafe intToInt64# :: Int# -> Int64#
776 foreign import "stg_int64ToInt" unsafe int64ToInt# :: Int64# -> Int#
777 foreign import "stg_negateInt64" unsafe negateInt64# :: Int64# -> Int64#
778 foreign import "stg_remInt64" unsafe remInt64# :: Int64# -> Int64# -> Int64#
779 foreign import "stg_quotInt64" unsafe quotInt64# :: Int64# -> Int64# -> Int64#
780 foreign import "stg_timesInt64" unsafe timesInt64# :: Int64# -> Int64# -> Int64#
781 foreign import "stg_minusInt64" unsafe minusInt64# :: Int64# -> Int64# -> Int64#
782 foreign import "stg_plusInt64" unsafe plusInt64# :: Int64# -> Int64# -> Int64#
783 foreign import "stg_gtInt64" unsafe stg_gtInt64 :: Int64# -> Int64# -> Int#
784 foreign import "stg_geInt64" unsafe stg_geInt64 :: Int64# -> Int64# -> Int#
785 foreign import "stg_neInt64" unsafe stg_neInt64 :: Int64# -> Int64# -> Int#
786 foreign import "stg_eqInt64" unsafe stg_eqInt64 :: Int64# -> Int64# -> Int#
787 foreign import "stg_leInt64" unsafe stg_leInt64 :: Int64# -> Int64# -> Int#
788 foreign import "stg_ltInt64" unsafe stg_ltInt64 :: Int64# -> Int64# -> Int#
789
790 #endif
791
792 --
793 -- Code that's independent of Int64 rep.
794 -- 
795 instance CCallable   Int64
796 instance CReturnable Int64
797
798 instance Enum Int64 where
799     succ i
800       | i == maxBound = succError "Int64"
801       | otherwise     = i+1
802
803     pred i
804       | i == minBound = predError "Int64"
805       | otherwise     = i-1
806
807     toEnum    i = intToInt64 i
808     fromEnum  x
809       | x >= intToInt64 (minBound::Int) && x <= intToInt64 (maxBound::Int)
810       = int64ToInt x
811       | otherwise
812       = fromEnumError "Int64" x
813
814     enumFrom e1        = map integerToInt64 [int64ToInteger e1 .. int64ToInteger (maxBound::Int64)]
815     enumFromTo e1 e2   = map integerToInt64 [int64ToInteger e1 .. int64ToInteger e2]
816     enumFromThen e1 e2 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger last]
817                        where 
818                           last :: Int64
819                           last 
820                            | e2 < e1   = minBound
821                            | otherwise = maxBound
822
823     enumFromThenTo e1 e2 e3 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger e3]
824
825 instance Show Int64 where
826     showsPrec p i64 = showsPrec p (int64ToInteger i64)
827
828 instance Read Int64 where
829   readsPrec _ s = [ (integerToInt64 x,r) | (x,r) <- readDec s ]
830
831 instance Ix Int64 where
832     range (m,n)          = [m..n]
833     index b@(m,_) i
834            | inRange b i = int64ToInt (i-m)
835            | otherwise   = indexError b i "Int64"
836     inRange (m,n) i      = m <= i && i <= n
837
838 instance Real Int64 where
839   toRational x = toInteger x % 1
840
841 #if WORD_SIZE_IN_BYTES == 8
842 instance Bits Int64 where
843   (I64# x) .&. (I64# y)   = I64# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
844   (I64# x) .|. (I64# y)   = I64# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
845   (I64# x) `xor` (I64# y) = I64# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
846   complement (I64# x)     = I64# (negateInt# x)
847   shift (I64# x) i@(I# i#)
848         | i > 0     = I64# (iShiftL# x  i#)
849         | otherwise = I64# (iShiftRA# x (negateInt# i#))
850   i64@(I64# x)  `rotate` (I# i)
851         | i ==# 0#    = i64
852         | i ># 0#     = 
853              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
854              I64# (word2Int# (
855                     (int2Word# (iShiftL# x i')) 
856                           `or#`
857                     (int2Word# (iShiftRA# (word2Int# (
858                                               (int2Word# x) 
859                                                   `and#` 
860                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
861                                           i2))))
862         | otherwise = rotate i64 (I# (64# +# i))
863           where
864            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
865            i2 = 64# -# i'
866            (I64# maxBound#) = maxBound
867   bitSize  _    = 64
868   isSigned _    = True
869
870 #else /* WORD_SIZE_IN_BYTES != 8 */
871
872 instance Bits Int64 where
873   (I64# x) .&. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `and64#` (int64ToWord64# y)))
874   (I64# x) .|. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `or64#`  (int64ToWord64# y)))
875   (I64# x) `xor` (I64# y) = I64# (word64ToInt64# ((int64ToWord64# x) `xor64#` (int64ToWord64# y)))
876   complement (I64# x)     = I64# (negateInt64# x)
877   shift (I64# x) i@(I# i#)
878         | i > 0     = I64# (iShiftL64# x  i#)
879         | otherwise = I64# (iShiftRA64# x (negateInt# i#))
880   i64@(I64# x)  `rotate` (I# i)
881         | i ==# 0#    = i64
882         | i ># 0#     = 
883              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
884              I64# (word64ToInt64# (
885                     (int64ToWord64# (iShiftL64# x i'))                    `or64#`
886                     (int64ToWord64# (iShiftRA64# (word64ToInt64# ((int64ToWord64# x)     `and64#` 
887                                                  (int64ToWord64# (maxBound# `minusInt64#` (pow2_64# i2 `plusInt64#` (intToInt64# 1#))))))
888                                                 i2))))
889         | otherwise = rotate i64 (I# (64# +# i))
890           where
891            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
892            i2 = 64# -# i'
893            (I64# maxBound#) = maxBound
894   bitSize  _    = 64
895   isSigned _    = True
896
897 foreign import "stg_not64" unsafe not64# :: Word64# -> Word64#
898 foreign import "stg_xor64" unsafe xor64# :: Word64# -> Word64# -> Word64#
899 foreign import "stg_or64" unsafe or64# :: Word64# -> Word64# -> Word64#
900 foreign import "stg_and64" unsafe and64# :: Word64# -> Word64# -> Word64#
901 foreign import "stg_shiftRL64" unsafe shiftRL64# :: Word64# -> Int# -> Word64#
902 foreign import "stg_iShiftRA64" unsafe iShiftRA64# :: Int64# -> Int# -> Int64#
903 foreign import "stg_iShiftRL64" unsafe iShiftRL64# :: Int64# -> Int# -> Int64#
904 foreign import "stg_iShiftL64" unsafe iShiftL64# :: Int64# -> Int# -> Int64#
905 foreign import "stg_shiftL64" unsafe shiftL64# :: Word64# -> Int# -> Word64#
906
907 #endif
908
909 -- ---------------------------------------------------------------------------
910 -- Miscellaneous Utilities
911 -- ---------------------------------------------------------------------------
912
913 absReal :: (Ord a, Num a) => a -> a
914 absReal x    | x >= 0    = x
915              | otherwise = -x
916
917 signumReal :: (Ord a, Num a) => a -> a
918 signumReal x | x == 0    =  0
919              | x > 0     =  1
920              | otherwise = -1
921 \end{code}