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