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