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