[project @ 2001-02-22 16:48:24 by qrczak]
[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
238
239 remInt8, quotInt8 :: Int8 -> Int8 -> Int8
240 remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `remInt#`  (i8ToInt# y)))
241 quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `quotInt#` (i8ToInt# y)))
242
243 instance Ix Int8 where
244     range (m,n)          = [m..n]
245     index b@(m,_) i
246               | inRange b i = int8ToInt (i - m)
247               | otherwise   = indexError b i "Int8"
248     inRange (m,n) i      = m <= i && i <= n
249
250 instance Enum Int8 where
251     succ i
252       | i == maxBound = succError "Int8"
253       | otherwise     = i+1
254     pred i
255       | i == minBound = predError "Int8"
256       | otherwise     = i-1
257
258     toEnum x
259       | x >= fromIntegral (minBound::Int8) && x <= fromIntegral (maxBound::Int8) 
260       = intToInt8 x
261       | otherwise
262       = toEnumError "Int8" x (minBound::Int8,maxBound::Int8)
263
264     fromEnum           = int8ToInt
265     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int8)]
266     enumFromThen e1 e2 = 
267              map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int8)]
268                 where 
269                    last 
270                      | e2 < e1   = minBound
271                      | otherwise = maxBound
272
273 instance Read Int8 where
274     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
275
276 instance Show Int8 where
277     showsPrec p i8 = showsPrec p (int8ToInt i8)
278
279 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
280 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
281
282 instance Bits Int8 where
283   (I8# x) .&. (I8# y) = I8# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
284   (I8# x) .|. (I8# y) = I8# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
285   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
286   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
287   shift (I8# x) i@(I# i#)
288         | i > 0     = I8# (intToInt8# (iShiftL# (i8ToInt# x)  i#))
289         | otherwise = I8# (intToInt8# (iShiftRA# (i8ToInt# x) (negateInt# i#)))
290   i8@(I8# x)  `rotate` (I# i)
291         | i ==# 0#    = i8
292         | i ># 0#     = 
293              I8# (intToInt8# ( word2Int#  (
294                      (int2Word# (iShiftL# (i8ToInt# x) i'))
295                              `or#`
296                      (int2Word# (iShiftRA# (word2Int# (
297                                                 (int2Word# x) `and#` 
298                                                 (int2Word# (0x100# -# pow2# i2))))
299                                           i2)))))
300         | otherwise = rotate i8 (I# (8# +# i))
301           where
302            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
303            i2 = 8# -# i'
304   bitSize  _    = 8
305   isSigned _    = True
306
307 pow2# :: Int# -> Int#
308 pow2# x# = iShiftL# 1# x#
309
310 pow2_64# :: Int# -> Int64#
311 pow2_64# x# = word64ToInt64# (shiftL64# (wordToWord64# (int2Word# 1#)) x#)
312
313 -- -----------------------------------------------------------------------------
314 -- Int16
315 -- -----------------------------------------------------------------------------
316
317 data Int16  = I16# Int#
318
319 instance CCallable Int16
320 instance CReturnable Int16
321
322 int16ToInt  (I16# x) = I# (i16ToInt# x)
323
324 i16ToInt# :: Int# -> Int#
325 i16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
326    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
327
328 -- This doesn't perform any bounds checking on the value it is passed,
329 -- nor its sign, i.e., show (intToInt8 131071) => "-1"
330 intToInt16 (I# x) = I16# (intToInt16# x)
331
332 intToInt16# :: Int# -> Int#
333 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
334
335 instance Eq  Int16     where
336   (I16# x#) == (I16# y#) = x# ==# y#
337   (I16# x#) /= (I16# y#) = x# /=# y#
338
339 instance Ord Int16 where
340   compare (I16# x#) (I16# y#) = compareInt# (i16ToInt# x#) (i16ToInt# y#)
341
342 instance Num Int16 where
343   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
344   (I16# x#) - (I16# y#) = I16# (intToInt16# (x# -# y#))
345   (I16# x#) * (I16# y#) = I16# (intToInt16# (x# *# y#))
346   negate i@(I16# x#) = 
347      if x# ==# 0#
348       then i
349       else I16# (0x10000# -# x#)
350   abs           = absReal
351   signum        = signumReal
352   fromInteger (S# i#)    = I16# (intToInt16# i#)
353   fromInteger (J# s# d#) = I16# (intToInt16# (integer2Int# s# d#))
354
355 instance Bounded Int16 where
356     minBound = 0x8000
357     maxBound = 0x7fff 
358
359 instance Real Int16 where
360     toRational x = toInteger x % 1
361
362 instance Integral Int16 where
363     div x y
364        | x > 0 && y < 0 = quotInt16 (x-y-1) y
365        | x < 0 && y > 0 = quotInt16 (x-y+1) y
366        | otherwise      = quotInt16 x y
367     quot x@(I16# _) y@(I16# y#)
368        | y# /=# 0#      = x `quotInt16` y
369        | otherwise      = divZeroError "quot{Int16}" x
370     rem x@(I16# _) y@(I16# y#)
371        | y# /=# 0#      = x `remInt16` y
372        | otherwise      = divZeroError "rem{Int16}" x
373     mod x y
374        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
375        | otherwise                        = r
376         where r = remInt16 x y
377
378     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
379     toInteger i16  = toInteger (int16ToInt i16)
380
381 remInt16, quotInt16 :: Int16 -> Int16 -> Int16
382 remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `remInt#` (i16ToInt# y)))
383 quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `quotInt#` (i16ToInt# y)))
384
385 instance Ix Int16 where
386     range (m,n)          = [m..n]
387     index b@(m,_) i
388               | inRange b i = int16ToInt (i - m)
389               | otherwise   = indexError b i "Int16"
390     inRange (m,n) i      = m <= i && i <= n
391
392 instance Enum Int16 where
393     succ i
394       | i == maxBound = succError "Int16"
395       | otherwise     = i+1
396
397     pred i
398       | i == minBound = predError "Int16"
399       | otherwise     = i-1
400
401     toEnum x
402       | x >= fromIntegral (minBound::Int16) && x <= fromIntegral (maxBound::Int16) 
403       = intToInt16 x
404       | otherwise
405       = toEnumError "Int16" x (minBound::Int16, maxBound::Int16)
406
407     fromEnum         = int16ToInt
408
409     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int16)]
410     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int16)]
411                           where last 
412                                   | e2 < e1   = minBound
413                                   | otherwise = maxBound
414
415 instance Read Int16 where
416     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
417
418 instance Show Int16 where
419     showsPrec p i16 = showsPrec p (int16ToInt i16)
420
421
422 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
423 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
424
425 instance Bits Int16 where
426   (I16# x) .&. (I16# y) = I16# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
427   (I16# x) .|. (I16# y) = I16# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
428   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
429   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
430   shift (I16# x) i@(I# i#)
431         | i > 0     = I16# (intToInt16# (iShiftL# (i16ToInt# x)  i#))
432         | otherwise = I16# (intToInt16# (iShiftRA# (i16ToInt# x) (negateInt# i#)))
433   i16@(I16# x)  `rotate` (I# i)
434         | i ==# 0#    = i16
435         | i ># 0#     = 
436              I16# (intToInt16# (word2Int# (
437                     (int2Word# (iShiftL# (i16ToInt# x) i')) 
438                              `or#`
439                     (int2Word# (iShiftRA# ( word2Int# (
440                                     (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
441                                           i2)))))
442         | otherwise = rotate i16 (I# (16# +# i))
443           where
444            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
445            i2 = 16# -# i'
446   bitSize  _        = 16
447   isSigned _        = True
448
449 -- -----------------------------------------------------------------------------
450 -- Int32
451 -- -----------------------------------------------------------------------------
452
453 data Int32  = I32# Int#
454
455 instance CCallable Int32
456 instance CReturnable Int32
457
458 int32ToInt  (I32# x) = I# (i32ToInt# x)
459
460 i32ToInt# :: Int# -> Int#
461 #if WORD_SIZE_IN_BYTES > 4
462 i32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
463    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
464 #else
465 i32ToInt# x = x
466 #endif
467
468 intToInt32 (I# x) = I32# (intToInt32# x)
469
470 intToInt32# :: Int# -> Int#
471 #if WORD_SIZE_IN_BYTES > 4
472 intToInt32# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffffffff#)
473 #else
474 intToInt32# i# = i#
475 #endif
476
477 instance Eq  Int32     where
478   (I32# x#) == (I32# y#) = x# ==# y#
479   (I32# x#) /= (I32# y#) = x# /=# y#
480
481 instance Ord Int32    where
482   compare (I32# x#) (I32# y#) = compareInt# (i32ToInt# x#) (i32ToInt# y#)
483
484 instance Num Int32 where
485   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
486   (I32# x#) - (I32# y#) = I32# (intToInt32# (x# -# y#))
487   (I32# x#) * (I32# y#) = I32# (intToInt32# (x# *# y#))
488 #if WORD_SIZE_IN_BYTES > 4
489   negate i@(I32# x)  = 
490       if x ==# 0#
491        then i
492        else I32# (intToInt32# (0x100000000# -# x'))
493 #else
494   negate (I32# x)  = I32# (negateInt# x)
495 #endif
496   abs           = absReal
497   signum        = signumReal
498   fromInteger (S# i#)    = I32# (intToInt32# i#)
499   fromInteger (J# s# d#) = I32# (intToInt32# (integer2Int# s# d#))
500
501
502 instance Bounded Int32 where 
503     minBound = int2Int32 minBound
504     maxBound = int2Int32 maxBound
505
506 int2Int32 :: Int -> Int32
507 int2Int32 (I# i#) = I32# (intToInt32# i#)
508
509 instance Real Int32 where
510     toRational x = toInteger x % 1
511
512 instance Integral Int32 where
513     div x y
514        | x > 0 && y < 0 = quotInt32 (x-y-1) y
515        | x < 0 && y > 0 = quotInt32 (x-y+1) y
516        | otherwise      = quotInt32 x y
517     quot x@(I32# _) y@(I32# y#)
518        | y# /=# 0#  = x `quotInt32` y
519        | otherwise  = divZeroError "quot{Int32}" x
520     rem x@(I32# _) y@(I32# y#)
521        | y# /=# 0#  = x `remInt32` y
522        | otherwise  = divZeroError "rem{Int32}" x
523     mod x y
524        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
525        | otherwise                        = r
526         where r = remInt32 x y
527
528     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
529     toInteger i32  = toInteger (int32ToInt i32)
530
531 remInt32, quotInt32 :: Int32 -> Int32 -> Int32
532 remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `remInt#`  (i32ToInt# y)))
533 quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `quotInt#` (i32ToInt# y)))
534
535 instance Ix Int32 where
536     range (m,n)          = [m..n]
537     index b@(m,_) i
538               | inRange b i = int32ToInt (i - m)
539               | otherwise   = indexError b i "Int32"
540     inRange (m,n) i      = m <= i && i <= n
541
542 instance Enum Int32 where
543     succ i
544       | i == maxBound = succError "Int32"
545       | otherwise     = i+1
546
547     pred i
548       | i == minBound = predError "Int32"
549       | otherwise     = i-1
550
551     toEnum x
552         -- with Int having the same range as Int32, the following test
553         -- shouldn't fail. However, having it here 
554       | x >= fromIntegral (minBound::Int32) && x <= fromIntegral (maxBound::Int32) 
555       = intToInt32 x
556       | otherwise
557       = toEnumError "Int32" x (minBound::Int32, maxBound::Int32)
558
559     fromEnum           = int32ToInt
560
561     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int32)]
562     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int32)]
563                           where 
564                             last
565                              | e2 < e1   = minBound
566                              | otherwise = maxBound
567
568
569 instance Read Int32 where
570     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
571
572 instance Show Int32 where
573     showsPrec p i32 = showsPrec p (int32ToInt i32)
574
575 instance Bits Int32 where
576   (I32# x) .&. (I32# y)   = I32# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
577   (I32# x) .|. (I32# y)   = I32# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
578   (I32# x) `xor` (I32# y) = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
579 #if WORD_SIZE_IN_BYTES > 4
580   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffffffff#)))
581 #else
582   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
583 #endif
584   shift (I32# x) i@(I# i#)
585         | i > 0     = I32# (intToInt32# (iShiftL# (i32ToInt# x)  i#))
586         | otherwise = I32# (intToInt32# (iShiftRA# (i32ToInt# x) (negateInt# i#)))
587   i32@(I32# x)  `rotate` (I# i)
588         | i ==# 0#    = i32
589         | i ># 0#     = 
590              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
591              I32# (intToInt32# ( word2Int# (
592                     (int2Word# (iShiftL# (i32ToInt# x) i')) 
593                           `or#`
594                     (int2Word# (iShiftRA# (word2Int# (
595                                               (int2Word# x) 
596                                                   `and#` 
597                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
598                                           i2)))))
599         | otherwise = rotate i32 (I# (32# +# i))
600           where
601            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
602            i2 = 32# -# i'
603            (I32# maxBound#) = maxBound
604   bitSize  _    = 32
605   isSigned _    = True
606
607 -- -----------------------------------------------------------------------------
608 -- Int64
609 -- -----------------------------------------------------------------------------
610
611 #if WORD_SIZE_IN_BYTES == 8
612 data Int64  = I64# Int#
613
614 int32ToInt64 (I32# i#) = I64# i#
615
616 intToInt32# :: Int# -> Int#
617 intToInt32# i# = word2Int# ((int2Word# i#) `and#` (case (maxBound::Word32) of W# x# -> x#))
618
619 int64ToInt32 (I64# i#) = I32# (intToInt32# w#)
620
621 instance Eq  Int64     where 
622   (I64# x) == (I64# y) = x `eqInt#` y
623   (I64# x) /= (I64# y) = x `neInt#` y
624
625 instance Ord Int32    where
626   compare (I64# x#) (I64# y#) = compareInt# x# y#
627
628 instance Num Int64 where
629   (I64# x) + (I64# y) = I64# (x +# y)
630   (I64# x) - (I64# y) = I64# (x -# y)
631   (I64# x) * (I64# y) = I64# (x *# y)
632   negate w@(I64# x)   = I64# (negateInt# x)
633   abs x               = absReal
634   signum              = signumReal
635   fromInteger (S# i#)    = I64# i#
636   fromInteger (J# s# d#) = I64# (integer2Int# s# d#)
637
638 instance Bounded Int64 where
639   minBound = integerToInt64 (-0x8000000000000000)
640   maxBound = integerToInt64 0x7fffffffffffffff
641
642 instance Integral Int64 where
643     div x y
644       | x > 0 && y < 0  = quotInt64 (x-y-1) y
645       | x < 0 && y > 0  = quotInt64 (x-y+1) y
646       | otherwise       = quotInt64 x y
647
648     quot x@(I64# _) y@(I64# y#)
649        | y# /=# 0# = x `quotInt64` y
650        | otherwise = divZeroError "quot{Int64}" x
651
652     rem x@(I64# _) y@(I64# y#)
653        | y# /=# 0# = x `remInt64` y
654        | otherwise = divZeroError "rem{Int64}" x
655
656     mod x y
657        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
658        | otherwise = r
659         where r = remInt64 x y
660
661     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
662     toInteger (I64# i#) = toInteger (I# i#)
663
664 remInt64  (I64# x) (I64# y) = I64# (x `remInt#` y)
665 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt#` y)
666
667 int64ToInteger (I64# i#) = toInteger (I# i#)
668 integerToInt64 i = case fromInteger i of { I# i# -> I64# i# }
669
670 intToInt64 (I# i#) = I64# i#
671 int64ToInt (I64# i#) = I# i#
672
673 #else
674 --assume: support for long-longs
675 data Int64 = I64# Int64#
676
677 int32ToInt64 (I32# i#) = I64# (intToInt64# i#)
678 int64ToInt32 (I64# i#) = I32# (int64ToInt# i#)
679
680 int64ToInteger (I64# x#) = 
681    case int64ToInteger# x# of
682      (# s#, p# #) -> J# s# p#
683
684 integerToInt64 (S# i#) = I64# (intToInt64# i#)
685 integerToInt64 (J# s# d#) = I64# (integerToInt64# s# d#)
686
687 instance Eq  Int64     where 
688   (I64# x) == (I64# y) = x `eqInt64#` y
689   (I64# x) /= (I64# y) = x `neInt64#` y
690
691 instance Ord Int64     where 
692   compare (I64# x) (I64# y)   = compareInt64# x y
693   (<)  (I64# x) (I64# y)      = x `ltInt64#` y
694   (<=) (I64# x) (I64# y)      = x `leInt64#` y
695   (>=) (I64# x) (I64# y)      = x `geInt64#` y
696   (>)  (I64# x) (I64# y)      = x `gtInt64#` y
697   max x@(I64# x#) y@(I64# y#) = 
698      case (compareInt64# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
699   min x@(I64# x#) y@(I64# y#) =
700      case (compareInt64# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
701
702 instance Num Int64 where
703   (I64# x) + (I64# y) = I64# (x `plusInt64#`  y)
704   (I64# x) - (I64# y) = I64# (x `minusInt64#` y)
705   (I64# x) * (I64# y) = I64# (x `timesInt64#` y)
706   negate (I64# x)     = I64# (negateInt64# x)
707   abs x               = absReal x
708   signum              = signumReal
709   fromInteger i       = integerToInt64 i
710
711 compareInt64# :: Int64# -> Int64# -> Ordering
712 compareInt64# i# j# 
713  | i# `ltInt64#` j# = LT
714  | i# `eqInt64#` j# = EQ
715  | otherwise        = GT
716
717 instance Bounded Int64 where
718   minBound = integerToInt64 (-0x8000000000000000)
719   maxBound = integerToInt64 0x7fffffffffffffff
720
721 instance Integral Int64 where
722     div x y
723       | x > 0 && y < 0  = quotInt64 (x-y-1) y
724       | x < 0 && y > 0  = quotInt64 (x-y+1) y
725       | otherwise       = quotInt64 x y
726
727     quot x@(I64# _) y@(I64# y#)
728        | y# `neInt64#` (intToInt64# 0#) = x `quotInt64` y
729        | otherwise = divZeroError "quot{Int64}" x
730
731     rem x@(I64# _) y@(I64# y#)
732        | y# `neInt64#` (intToInt64# 0#) = x `remInt64` y
733        | otherwise = divZeroError "rem{Int64}" x
734
735     mod x y
736        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
737        | otherwise = r
738         where r = remInt64 x y
739
740     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
741     toInteger i         = int64ToInteger i
742
743 remInt64, quotInt64 :: Int64 -> Int64 -> Int64
744 remInt64  (I64# x) (I64# y) = I64# (x `remInt64#` y)
745 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt64#` y)
746
747 intToInt64 (I# i#) = I64# (intToInt64# i#)
748 int64ToInt (I64# i#) = I# (int64ToInt# i#)
749
750 -- Int64# primop wrappers:
751
752 ltInt64# :: Int64# -> Int64# -> Bool
753 ltInt64# x# y# = stg_ltInt64 x# y# /=# 0#
754       
755 leInt64# :: Int64# -> Int64# -> Bool
756 leInt64# x# y# = stg_leInt64 x# y# /=# 0#
757
758 eqInt64# :: Int64# -> Int64# -> Bool
759 eqInt64# x# y# = stg_eqInt64 x# y# /=# 0#
760
761 neInt64# :: Int64# -> Int64# -> Bool
762 neInt64# x# y# = stg_neInt64 x# y# /=# 0#
763
764 geInt64# :: Int64# -> Int64# -> Bool
765 geInt64# x# y# = stg_geInt64 x# y# /=# 0#
766
767 gtInt64# :: Int64# -> Int64# -> Bool
768 gtInt64# x# y# = stg_gtInt64 x# y# /=# 0#
769
770 foreign import "stg_intToInt64" unsafe intToInt64# :: Int# -> Int64#
771 foreign import "stg_int64ToInt" unsafe int64ToInt# :: Int64# -> Int#
772 foreign import "stg_negateInt64" unsafe negateInt64# :: Int64# -> Int64#
773 foreign import "stg_remInt64" unsafe remInt64# :: Int64# -> Int64# -> Int64#
774 foreign import "stg_quotInt64" unsafe quotInt64# :: Int64# -> Int64# -> Int64#
775 foreign import "stg_timesInt64" unsafe timesInt64# :: Int64# -> Int64# -> Int64#
776 foreign import "stg_minusInt64" unsafe minusInt64# :: Int64# -> Int64# -> Int64#
777 foreign import "stg_plusInt64" unsafe plusInt64# :: Int64# -> Int64# -> Int64#
778 foreign import "stg_gtInt64" unsafe stg_gtInt64 :: Int64# -> Int64# -> Int#
779 foreign import "stg_geInt64" unsafe stg_geInt64 :: Int64# -> Int64# -> Int#
780 foreign import "stg_neInt64" unsafe stg_neInt64 :: Int64# -> Int64# -> Int#
781 foreign import "stg_eqInt64" unsafe stg_eqInt64 :: Int64# -> Int64# -> Int#
782 foreign import "stg_leInt64" unsafe stg_leInt64 :: Int64# -> Int64# -> Int#
783 foreign import "stg_ltInt64" unsafe stg_ltInt64 :: Int64# -> Int64# -> Int#
784
785 #endif
786
787 --
788 -- Code that's independent of Int64 rep.
789 -- 
790 instance CCallable   Int64
791 instance CReturnable Int64
792
793 instance Enum Int64 where
794     succ i
795       | i == maxBound = succError "Int64"
796       | otherwise     = i+1
797
798     pred i
799       | i == minBound = predError "Int64"
800       | otherwise     = i-1
801
802     toEnum    i = intToInt64 i
803     fromEnum  x
804       | x >= intToInt64 (minBound::Int) && x <= intToInt64 (maxBound::Int)
805       = int64ToInt x
806       | otherwise
807       = fromEnumError "Int64" x
808
809     enumFrom e1        = map integerToInt64 [int64ToInteger e1 .. int64ToInteger (maxBound::Int64)]
810     enumFromTo e1 e2   = map integerToInt64 [int64ToInteger e1 .. int64ToInteger e2]
811     enumFromThen e1 e2 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger last]
812                        where 
813                           last :: Int64
814                           last 
815                            | e2 < e1   = minBound
816                            | otherwise = maxBound
817
818     enumFromThenTo e1 e2 e3 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger e3]
819
820 instance Show Int64 where
821     showsPrec p i64 = showsPrec p (int64ToInteger i64)
822
823 instance Read Int64 where
824   readsPrec _ s = [ (integerToInt64 x,r) | (x,r) <- readDec s ]
825
826 instance Ix Int64 where
827     range (m,n)          = [m..n]
828     index b@(m,_) i
829            | inRange b i = int64ToInt (i-m)
830            | otherwise   = indexError b i "Int64"
831     inRange (m,n) i      = m <= i && i <= n
832
833 instance Real Int64 where
834   toRational x = toInteger x % 1
835
836 #if WORD_SIZE_IN_BYTES == 8
837 instance Bits Int64 where
838   (I64# x) .&. (I64# y)   = I64# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
839   (I64# x) .|. (I64# y)   = I64# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
840   (I64# x) `xor` (I64# y) = I64# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
841   complement (I64# x)     = I64# (negateInt# x)
842   shift (I64# x) i@(I# i#)
843         | i > 0     = I64# (iShiftL# x  i#)
844         | otherwise = I64# (iShiftRA# x (negateInt# i#))
845   i64@(I64# x)  `rotate` (I# i)
846         | i ==# 0#    = i64
847         | i ># 0#     = 
848              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
849              I64# (word2Int# (
850                     (int2Word# (iShiftL# x i')) 
851                           `or#`
852                     (int2Word# (iShiftRA# (word2Int# (
853                                               (int2Word# x) 
854                                                   `and#` 
855                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
856                                           i2))))
857         | otherwise = rotate i64 (I# (64# +# i))
858           where
859            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
860            i2 = 64# -# i'
861            (I64# maxBound#) = maxBound
862   bitSize  _    = 64
863   isSigned _    = True
864
865 #else /* WORD_SIZE_IN_BYTES != 8 */
866
867 instance Bits Int64 where
868   (I64# x) .&. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `and64#` (int64ToWord64# y)))
869   (I64# x) .|. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `or64#`  (int64ToWord64# y)))
870   (I64# x) `xor` (I64# y) = I64# (word64ToInt64# ((int64ToWord64# x) `xor64#` (int64ToWord64# y)))
871   complement (I64# x)     = I64# (negateInt64# x)
872   shift (I64# x) i@(I# i#)
873         | i > 0     = I64# (iShiftL64# x  i#)
874         | otherwise = I64# (iShiftRA64# x (negateInt# i#))
875   i64@(I64# x)  `rotate` (I# i)
876         | i ==# 0#    = i64
877         | i ># 0#     = 
878              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
879              I64# (word64ToInt64# (
880                     (int64ToWord64# (iShiftL64# x i'))                    `or64#`
881                     (int64ToWord64# (iShiftRA64# (word64ToInt64# ((int64ToWord64# x)     `and64#` 
882                                                  (int64ToWord64# (maxBound# `minusInt64#` (pow2_64# i2 `plusInt64#` (intToInt64# 1#))))))
883                                                 i2))))
884         | otherwise = rotate i64 (I# (64# +# i))
885           where
886            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
887            i2 = 64# -# i'
888            (I64# maxBound#) = maxBound
889   bitSize  _    = 64
890   isSigned _    = True
891
892 foreign import "stg_not64" unsafe not64# :: Word64# -> Word64#
893 foreign import "stg_xor64" unsafe xor64# :: Word64# -> Word64# -> Word64#
894 foreign import "stg_or64" unsafe or64# :: Word64# -> Word64# -> Word64#
895 foreign import "stg_and64" unsafe and64# :: Word64# -> Word64# -> Word64#
896 foreign import "stg_shiftRL64" unsafe shiftRL64# :: Word64# -> Int# -> Word64#
897 foreign import "stg_iShiftRA64" unsafe iShiftRA64# :: Int64# -> Int# -> Int64#
898 foreign import "stg_iShiftRL64" unsafe iShiftRL64# :: Int64# -> Int# -> Int64#
899 foreign import "stg_iShiftL64" unsafe iShiftL64# :: Int64# -> Int# -> Int64#
900 foreign import "stg_shiftL64" unsafe shiftL64# :: Word64# -> Int# -> Word64#
901
902 #endif
903
904 -- ---------------------------------------------------------------------------
905 -- Miscellaneous Utilities
906 -- ---------------------------------------------------------------------------
907
908 absReal :: (Ord a, Num a) => a -> a
909 absReal x    | x >= 0    = x
910              | otherwise = -x
911
912 signumReal :: (Ord a, Num a) => a -> a
913 signumReal x | x == 0    =  0
914              | x > 0     =  1
915              | otherwise = -1
916 \end{code}