[project @ 2001-04-03 15:05:52 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelInt.lhs
1 %
2 % (c) The University of Glasgow, 1997-2001
3 %
4 \section[PrelInt]{Module @PrelInt@}
5
6 \begin{code}
7 #include "MachDeps.h"
8
9 module PrelInt (
10     Int8(..), Int16(..), Int32(..), Int64(..))
11     where
12
13 import PrelBase
14 import PrelEnum
15 import PrelNum
16 import PrelReal
17 import PrelRead
18 import PrelArr
19 import PrelBits
20 import PrelWord
21
22 ------------------------------------------------------------------------
23 -- type Int8
24 ------------------------------------------------------------------------
25
26 -- Int8 is represented in the same way as Int. Operations may assume
27 -- and must ensure that it holds only values from its logical range.
28
29 data Int8 = I8# Int# deriving (Eq, Ord)
30
31 instance CCallable Int8
32 instance CReturnable Int8
33
34 instance Show Int8 where
35     showsPrec p x = showsPrec p (fromIntegral x :: Int)
36
37 instance Num Int8 where
38     (I8# x#) + (I8# y#)    = I8# (intToInt8# (x# +# y#))
39     (I8# x#) - (I8# y#)    = I8# (intToInt8# (x# -# y#))
40     (I8# x#) * (I8# y#)    = I8# (intToInt8# (x# *# y#))
41     negate (I8# x#)        = I8# (intToInt8# (negateInt# x#))
42     abs x | x >= 0         = x
43           | otherwise      = negate x
44     signum x | x > 0       = 1
45     signum 0               = 0
46     signum _               = -1
47     fromInteger (S# i#)    = I8# (intToInt8# i#)
48     fromInteger (J# s# d#) = I8# (intToInt8# (integer2Int# s# d#))
49
50 instance Real Int8 where
51     toRational x = toInteger x % 1
52
53 instance Enum Int8 where
54     succ x
55         | x /= maxBound = x + 1
56         | otherwise     = succError "Int8"
57     pred x
58         | x /= minBound = x - 1
59         | otherwise     = predError "Int8"
60     toEnum i@(I# i#)
61         | i >= fromIntegral (minBound::Int8) && i <= fromIntegral (maxBound::Int8)
62                         = I8# i#
63         | otherwise     = toEnumError "Int8" i (minBound::Int8, maxBound::Int8)
64     fromEnum (I8# x#)   = I# x#
65     enumFrom            = boundedEnumFrom
66     enumFromThen        = boundedEnumFromThen
67
68 instance Integral Int8 where
69     quot    x@(I8# x#) y@(I8# y#)
70         | y /= 0                  = I8# (intToInt8# (x# `quotInt#` y#))
71         | otherwise               = divZeroError "quot{Int8}" x
72     rem     x@(I8# x#) y@(I8# y#)
73         | y /= 0                  = I8# (intToInt8# (x# `remInt#` y#))
74         | otherwise               = divZeroError "rem{Int8}" x
75     div     x@(I8# x#) y@(I8# y#)
76         | y /= 0                  = I8# (intToInt8# (x# `divInt#` y#))
77         | otherwise               = divZeroError "div{Int8}" x
78     mod     x@(I8# x#) y@(I8# y#)
79         | y /= 0                  = I8# (intToInt8# (x# `modInt#` y#))
80         | otherwise               = divZeroError "mod{Int8}" x
81     quotRem x@(I8# x#) y@(I8# y#)
82         | y /= 0                  = (I8# (intToInt8# (x# `quotInt#` y#)),
83                                     I8# (intToInt8# (x# `remInt#` y#)))
84         | otherwise               = divZeroError "quotRem{Int8}" x
85     divMod  x@(I8# x#) y@(I8# y#)
86         | y /= 0                  = (I8# (intToInt8# (x# `divInt#` y#)),
87                                     I8# (intToInt8# (x# `modInt#` y#)))
88         | otherwise               = divZeroError "divMod{Int8}" x
89     toInteger (I8# x#)            = S# x#
90
91 instance Bounded Int8 where
92     minBound = -0x80
93     maxBound =  0x7F
94
95 instance Ix Int8 where
96     range (m,n)       = [m..n]
97     index b@(m,_) i
98         | inRange b i = fromIntegral (i - m)
99         | otherwise   = indexError b i "Int8"
100     inRange (m,n) i   = m <= i && i <= n
101
102 instance Read Int8 where
103     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
104
105 instance Bits Int8 where
106     (I8# x#) .&.   (I8# y#)   = I8# (word2Int# (int2Word# x# `and#` int2Word# y#))
107     (I8# x#) .|.   (I8# y#)   = I8# (word2Int# (int2Word# x# `or#`  int2Word# y#))
108     (I8# x#) `xor` (I8# y#)   = I8# (word2Int# (int2Word# x# `xor#` int2Word# y#))
109     complement (I8# x#)       = I8# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
110     (I8# x#) `shift` (I# i#)
111         | i# >=# 0#           = I8# (intToInt8# (x# `iShiftL#` i#))
112         | otherwise           = I8# (x# `iShiftRA#` negateInt# i#)
113     (I8# x#) `rotate` (I# i#) =
114         I8# (intToInt8# (word2Int# ((x'# `shiftL#` i'#) `or#`
115                                     (x'# `shiftRL#` (8# -# i'#)))))
116         where
117         x'# = wordToWord8# (int2Word# x#)
118         i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
119     bitSize  _                = 8
120     isSigned _                = True
121
122 {-# RULES
123 "fromIntegral/a->Int8" fromIntegral = \x -> case fromIntegral x of I# x# -> I8# (intToInt8# x#)
124 "fromIntegral/Int8->a" fromIntegral = \(I8# x#) -> fromIntegral (I# x#)
125     #-}
126
127 ------------------------------------------------------------------------
128 -- type Int16
129 ------------------------------------------------------------------------
130
131 -- Int16 is represented in the same way as Int. Operations may assume
132 -- and must ensure that it holds only values from its logical range.
133
134 data Int16 = I16# Int# deriving (Eq, Ord)
135
136 instance CCallable Int16
137 instance CReturnable Int16
138
139 instance Show Int16 where
140     showsPrec p x = showsPrec p (fromIntegral x :: Int)
141
142 instance Num Int16 where
143     (I16# x#) + (I16# y#)  = I16# (intToInt16# (x# +# y#))
144     (I16# x#) - (I16# y#)  = I16# (intToInt16# (x# -# y#))
145     (I16# x#) * (I16# y#)  = I16# (intToInt16# (x# *# y#))
146     negate (I16# x#)       = I16# (intToInt16# (negateInt# x#))
147     abs x | x >= 0         = x
148           | otherwise      = negate x
149     signum x | x > 0       = 1
150     signum 0               = 0
151     signum _               = -1
152     fromInteger (S# i#)    = I16# (intToInt16# i#)
153     fromInteger (J# s# d#) = I16# (intToInt16# (integer2Int# s# d#))
154
155 instance Real Int16 where
156     toRational x = toInteger x % 1
157
158 instance Enum Int16 where
159     succ x
160         | x /= maxBound = x + 1
161         | otherwise     = succError "Int16"
162     pred x
163         | x /= minBound = x - 1
164         | otherwise     = predError "Int16"
165     toEnum i@(I# i#)
166         | i >= fromIntegral (minBound::Int16) && i <= fromIntegral (maxBound::Int16)
167                         = I16# i#
168         | otherwise     = toEnumError "Int16" i (minBound::Int16, maxBound::Int16)
169     fromEnum (I16# x#)  = I# x#
170     enumFrom            = boundedEnumFrom
171     enumFromThen        = boundedEnumFromThen
172
173 instance Integral Int16 where
174     quot    x@(I16# x#) y@(I16# y#)
175         | y /= 0                  = I16# (intToInt16# (x# `quotInt#` y#))
176         | otherwise               = divZeroError "quot{Int16}" x
177     rem     x@(I16# x#) y@(I16# y#)
178         | y /= 0                  = I16# (intToInt16# (x# `remInt#` y#))
179         | otherwise               = divZeroError "rem{Int16}" x
180     div     x@(I16# x#) y@(I16# y#)
181         | y /= 0                  = I16# (intToInt16# (x# `divInt#` y#))
182         | otherwise               = divZeroError "div{Int16}" x
183     mod     x@(I16# x#) y@(I16# y#)
184         | y /= 0                  = I16# (intToInt16# (x# `modInt#` y#))
185         | otherwise               = divZeroError "mod{Int16}" x
186     quotRem x@(I16# x#) y@(I16# y#)
187         | y /= 0                  = (I16# (intToInt16# (x# `quotInt#` y#)),
188                                     I16# (intToInt16# (x# `remInt#` y#)))
189         | otherwise               = divZeroError "quotRem{Int16}" x
190     divMod  x@(I16# x#) y@(I16# y#)
191         | y /= 0                  = (I16# (intToInt16# (x# `divInt#` y#)),
192                                     I16# (intToInt16# (x# `modInt#` y#)))
193         | otherwise               = divZeroError "divMod{Int16}" x
194     toInteger (I16# x#)           = S# x#
195
196 instance Bounded Int16 where
197     minBound = -0x8000
198     maxBound =  0x7FFF
199
200 instance Ix Int16 where
201     range (m,n)       = [m..n]
202     index b@(m,_) i
203         | inRange b i = fromIntegral (i - m)
204         | otherwise   = indexError b i "Int16"
205     inRange (m,n) i   = m <= i && i <= n
206
207 instance Read Int16 where
208     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
209
210 instance Bits Int16 where
211     (I16# x#) .&.   (I16# y#)  = I16# (word2Int# (int2Word# x# `and#` int2Word# y#))
212     (I16# x#) .|.   (I16# y#)  = I16# (word2Int# (int2Word# x# `or#`  int2Word# y#))
213     (I16# x#) `xor` (I16# y#)  = I16# (word2Int# (int2Word# x# `xor#` int2Word# y#))
214     complement (I16# x#)       = I16# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
215     (I16# x#) `shift` (I# i#)
216         | i# >=# 0#            = I16# (intToInt16# (x# `iShiftL#` i#))
217         | otherwise            = I16# (x# `iShiftRA#` negateInt# i#)
218     (I16# x#) `rotate` (I# i#) =
219         I16# (intToInt16# (word2Int# ((x'# `shiftL#` i'#) `or#`
220                                       (x'# `shiftRL#` (16# -# i'#)))))
221         where
222         x'# = wordToWord16# (int2Word# x#)
223         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
224     bitSize  _                 = 16
225     isSigned _                 = True
226
227 {-# RULES
228 "fromIntegral/a->Int16" fromIntegral = \x -> case fromIntegral x of I# x# -> I16# (intToInt16# x#)
229 "fromIntegral/Int16->a" fromIntegral = \(I16# x#) -> fromIntegral (I# x#)
230     #-}
231
232 ------------------------------------------------------------------------
233 -- type Int32
234 ------------------------------------------------------------------------
235
236 -- Int32 is represented in the same way as Int.
237 #if WORD_SIZE_IN_BYTES == 8
238 -- Operations may assume and must ensure that it holds only values
239 -- from its logical range.
240 #endif
241
242 data Int32 = I32# Int# deriving (Eq, Ord)
243
244 instance CCallable Int32
245 instance CReturnable Int32
246
247 instance Show Int32 where
248     showsPrec p x = showsPrec p (fromIntegral x :: Int)
249
250 instance Num Int32 where
251     (I32# x#) + (I32# y#)  = I32# (intToInt32# (x# +# y#))
252     (I32# x#) - (I32# y#)  = I32# (intToInt32# (x# -# y#))
253     (I32# x#) * (I32# y#)  = I32# (intToInt32# (x# *# y#))
254     negate (I32# x#)       = I32# (intToInt32# (negateInt# x#))
255     abs x | x >= 0         = x
256           | otherwise      = negate x
257     signum x | x > 0       = 1
258     signum 0               = 0
259     signum _               = -1
260     fromInteger (S# i#)    = I32# (intToInt32# i#)
261     fromInteger (J# s# d#) = I32# (intToInt32# (integer2Int# s# d#))
262
263 instance Real Int32 where
264     toRational x = toInteger x % 1
265
266 instance Enum Int32 where
267     succ x
268         | x /= maxBound = x + 1
269         | otherwise     = succError "Int32"
270     pred x
271         | x /= minBound = x - 1
272         | otherwise     = predError "Int32"
273 #if WORD_SIZE_IN_BYTES == 4
274     toEnum (I# i#)      = I32# i#
275 #else
276     toEnum i@(I# i#)
277         | i >= fromIntegral (minBound::Int32) && i <= fromIntegral (maxBound::Int32)
278                         = I32# i#
279         | otherwise     = toEnumError "Int32" i (minBound::Int32, maxBound::Int32)
280 #endif
281     fromEnum (I32# x#)  = I# x#
282     enumFrom            = boundedEnumFrom
283     enumFromThen        = boundedEnumFromThen
284
285 instance Integral Int32 where
286     quot    x@(I32# x#) y@(I32# y#)
287         | y /= 0                  = I32# (intToInt32# (x# `quotInt#` y#))
288         | otherwise               = divZeroError "quot{Int32}" x
289     rem     x@(I32# x#) y@(I32# y#)
290         | y /= 0                  = I32# (intToInt32# (x# `remInt#` y#))
291         | otherwise               = divZeroError "rem{Int32}" x
292     div     x@(I32# x#) y@(I32# y#)
293         | y /= 0                  = I32# (intToInt32# (x# `divInt#` y#))
294         | otherwise               = divZeroError "div{Int32}" x
295     mod     x@(I32# x#) y@(I32# y#)
296         | y /= 0                  = I32# (intToInt32# (x# `modInt#` y#))
297         | otherwise               = divZeroError "mod{Int32}" x
298     quotRem x@(I32# x#) y@(I32# y#)
299         | y /= 0                  = (I32# (intToInt32# (x# `quotInt#` y#)),
300                                     I32# (intToInt32# (x# `remInt#` y#)))
301         | otherwise               = divZeroError "quotRem{Int32}" x
302     divMod  x@(I32# x#) y@(I32# y#)
303         | y /= 0                  = (I32# (intToInt32# (x# `divInt#` y#)),
304                                     I32# (intToInt32# (x# `modInt#` y#)))
305         | otherwise               = divZeroError "divMod{Int32}" x
306     toInteger (I32# x#)           = S# x#
307
308 instance Bounded Int32 where
309     minBound = -0x80000000
310     maxBound =  0x7FFFFFFF
311
312 instance Ix Int32 where
313     range (m,n)       = [m..n]
314     index b@(m,_) i
315         | inRange b i = fromIntegral (i - m)
316         | otherwise   = indexError b i "Int32"
317     inRange (m,n) i   = m <= i && i <= n
318
319 instance Read Int32 where
320     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
321
322 instance Bits Int32 where
323     (I32# x#) .&.   (I32# y#)  = I32# (word2Int# (int2Word# x# `and#` int2Word# y#))
324     (I32# x#) .|.   (I32# y#)  = I32# (word2Int# (int2Word# x# `or#`  int2Word# y#))
325     (I32# x#) `xor` (I32# y#)  = I32# (word2Int# (int2Word# x# `xor#` int2Word# y#))
326     complement (I32# x#)       = I32# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
327     (I32# x#) `shift` (I# i#)
328         | i# >=# 0#            = I32# (intToInt32# (x# `iShiftL#` i#))
329         | otherwise            = I32# (x# `iShiftRA#` negateInt# i#)
330     (I32# x#) `rotate` (I# i#) =
331         I32# (intToInt32# (word2Int# ((x'# `shiftL#` i'#) `or#`
332                                       (x'# `shiftRL#` (32# -# i'#)))))
333         where
334         x'# = wordToWord32# (int2Word# x#)
335         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
336     bitSize  _                 = 32
337     isSigned _                 = True
338
339 {-# RULES
340 "fromIntegral/a->Int32" fromIntegral = \x -> case fromIntegral x of I# x# -> I32# (intToInt32# x#)
341 "fromIntegral/Int32->a" fromIntegral = \(I32# x#) -> fromIntegral (I# x#)
342     #-}
343
344 ------------------------------------------------------------------------
345 -- type Int64
346 ------------------------------------------------------------------------
347
348 #if WORD_SIZE_IN_BYTES == 4
349
350 data Int64 = I64# Int64#
351
352 instance Eq Int64 where
353     (I64# x#) == (I64# y#) = x# `eqInt64#` y#
354     (I64# x#) /= (I64# y#) = x# `neInt64#` y#
355
356 instance Ord Int64 where
357     (I64# x#) <  (I64# y#) = x# `ltInt64#` y#
358     (I64# x#) <= (I64# y#) = x# `leInt64#` y#
359     (I64# x#) >  (I64# y#) = x# `gtInt64#` y#
360     (I64# x#) >= (I64# y#) = x# `geInt64#` y#
361
362 instance Show Int64 where
363     showsPrec p x = showsPrec p (toInteger x)
364
365 instance Num Int64 where
366     (I64# x#) + (I64# y#)  = I64# (x# `plusInt64#`  y#)
367     (I64# x#) - (I64# y#)  = I64# (x# `minusInt64#` y#)
368     (I64# x#) * (I64# y#)  = I64# (x# `timesInt64#` y#)
369     negate (I64# x#)       = I64# (negateInt64# x#)
370     abs x | x >= 0         = x
371           | otherwise      = negate x
372     signum x | x > 0       = 1
373     signum 0               = 0
374     signum _               = -1
375     fromInteger (S# i#)    = I64# (intToInt64# i#)
376     fromInteger (J# s# d#) = I64# (integerToInt64# s# d#)
377
378 instance Enum Int64 where
379     succ x
380         | x /= maxBound = x + 1
381         | otherwise     = succError "Int64"
382     pred x
383         | x /= minBound = x - 1
384         | otherwise     = predError "Int64"
385     toEnum (I# i#)      = I64# (intToInt64# i#)
386     fromEnum x@(I64# x#)
387         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
388                         = I# (int64ToInt# x#)
389         | otherwise     = fromEnumError "Int64" x
390     enumFrom            = integralEnumFrom
391     enumFromThen        = integralEnumFromThen
392     enumFromTo          = integralEnumFromTo
393     enumFromThenTo      = integralEnumFromThenTo
394
395 instance Integral Int64 where
396     quot    x@(I64# x#) y@(I64# y#)
397         | y /= 0                  = I64# (x# `quotInt64#` y#)
398         | otherwise               = divZeroError "quot{Int64}" x
399     rem     x@(I64# x#) y@(I64# y#)
400         | y /= 0                  = I64# (x# `remInt64#` y#)
401         | otherwise               = divZeroError "rem{Int64}" x
402     div     x@(I64# x#) y@(I64# y#)
403         | y /= 0                  = I64# (x# `divInt64#` y#)
404         | otherwise               = divZeroError "div{Int64}" x
405     mod     x@(I64# x#) y@(I64# y#)
406         | y /= 0                  = I64# (x# `modInt64#` y#)
407         | otherwise               = divZeroError "mod{Int64}" x
408     quotRem x@(I64# x#) y@(I64# y#)
409         | y /= 0                  = (I64# (x# `quotInt64#` y#), I64# (x# `remInt64#` y#))
410         | otherwise               = divZeroError "quotRem{Int64}" x
411     divMod  x@(I64# x#) y@(I64# y#)
412         | y /= 0                  = (I64# (x# `divInt64#` y#), I64# (x# `modInt64#` y#))
413         | otherwise               = divZeroError "divMod{Int64}" x
414     toInteger x@(I64# x#)
415         | x >= -0x80000000 && x <= 0x7FFFFFFF
416                                   = S# (int64ToInt# x#)
417         | otherwise               = case int64ToInteger# x# of (# s, d #) -> J# s d
418
419 divInt64#, modInt64# :: Int64# -> Int64# -> Int64#
420 x# `divInt64#` y#
421     | (x# `gtInt64#` intToInt64# 0#) && (y# `ltInt64#` intToInt64# 0#)
422         = ((x# `minusInt64#` y#) `minusInt64#` intToInt64# 1#) `quotInt64#` y#
423     | (x# `ltInt64#` intToInt64# 0#) && (y# `gtInt64#` intToInt64# 0#)
424         = ((x# `minusInt64#` y#) `plusInt64#` intToInt64# 1#) `quotInt64#` y#
425     | otherwise                = x# `quotInt64#` y#
426 x# `modInt64#` y#
427     | (x# `gtInt64#` intToInt64# 0#) && (y# `ltInt64#` intToInt64# 0#) ||
428       (x# `ltInt64#` intToInt64# 0#) && (y# `gtInt64#` intToInt64# 0#)
429         = if r# `neInt64#` intToInt64# 0# then r# `plusInt64#` y# else intToInt64# 0#
430     | otherwise = r#
431     where
432     r# = x# `remInt64#` y#
433
434 instance Read Int64 where
435     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
436
437 instance Bits Int64 where
438     (I64# x#) .&.   (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `and64#` int64ToWord64# y#))
439     (I64# x#) .|.   (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `or64#`  int64ToWord64# y#))
440     (I64# x#) `xor` (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `xor64#` int64ToWord64# y#))
441     complement (I64# x#)       = I64# (word64ToInt64# (not64# (int64ToWord64# x#)))
442     (I64# x#) `shift` (I# i#)
443         | i# >=# 0#            = I64# (x# `iShiftL64#` i#)
444         | otherwise            = I64# (x# `iShiftRA64#` negateInt# i#)
445     (I64# x#) `rotate` (I# i#) =
446         I64# (word64ToInt64# ((x'# `shiftL64#` i'#) `or64#`
447                               (x'# `shiftRL64#` (64# -# i'#))))
448         where
449         x'# = int64ToWord64# x#
450         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
451     bitSize  _                 = 64
452     isSigned _                 = True
453
454 foreign import "stg_eqInt64"       unsafe eqInt64#       :: Int64# -> Int64# -> Bool
455 foreign import "stg_neInt64"       unsafe neInt64#       :: Int64# -> Int64# -> Bool
456 foreign import "stg_ltInt64"       unsafe ltInt64#       :: Int64# -> Int64# -> Bool
457 foreign import "stg_leInt64"       unsafe leInt64#       :: Int64# -> Int64# -> Bool
458 foreign import "stg_gtInt64"       unsafe gtInt64#       :: Int64# -> Int64# -> Bool
459 foreign import "stg_geInt64"       unsafe geInt64#       :: Int64# -> Int64# -> Bool
460 foreign import "stg_plusInt64"     unsafe plusInt64#     :: Int64# -> Int64# -> Int64#
461 foreign import "stg_minusInt64"    unsafe minusInt64#    :: Int64# -> Int64# -> Int64#
462 foreign import "stg_timesInt64"    unsafe timesInt64#    :: Int64# -> Int64# -> Int64#
463 foreign import "stg_negateInt64"   unsafe negateInt64#   :: Int64# -> Int64#
464 foreign import "stg_quotInt64"     unsafe quotInt64#     :: Int64# -> Int64# -> Int64#
465 foreign import "stg_remInt64"      unsafe remInt64#      :: Int64# -> Int64# -> Int64#
466 foreign import "stg_intToInt64"    unsafe intToInt64#    :: Int# -> Int64#
467 foreign import "stg_int64ToInt"    unsafe int64ToInt#    :: Int64# -> Int#
468 foreign import "stg_wordToWord64"  unsafe wordToWord64#  :: Word# -> Word64#
469 foreign import "stg_word64ToWord"  unsafe word64ToWord#  :: Word64# -> Word#
470 foreign import "stg_int64ToWord64" unsafe int64ToWord64# :: Int64# -> Word64#
471 foreign import "stg_word64ToInt64" unsafe word64ToInt64# :: Word64# -> Int64#
472 foreign import "stg_and64"         unsafe and64#         :: Word64# -> Word64# -> Word64#
473 foreign import "stg_or64"          unsafe or64#          :: Word64# -> Word64# -> Word64#
474 foreign import "stg_xor64"         unsafe xor64#         :: Word64# -> Word64# -> Word64#
475 foreign import "stg_not64"         unsafe not64#         :: Word64# -> Word64#
476 foreign import "stg_iShiftL64"     unsafe iShiftL64#     :: Int64# -> Int# -> Int64#
477 foreign import "stg_iShiftRA64"    unsafe iShiftRA64#    :: Int64# -> Int# -> Int64#
478 foreign import "stg_shiftL64"      unsafe shiftL64#      :: Word64# -> Int# -> Word64#
479 foreign import "stg_shiftRL64"     unsafe shiftRL64#     :: Word64# -> Int# -> Word64#
480
481 {-# RULES
482 "fromIntegral/Int->Int64"    fromIntegral = \(I#   x#) -> I64# (intToInt64# x#)
483 "fromIntegral/Word->Int64"   fromIntegral = \(W#   x#) -> I64# (word64ToInt64# (wordToWord64# x#))
484 "fromIntegral/Word64->Int64" fromIntegral = \(W64# x#) -> I64# (word64ToInt64# x#)
485 "fromIntegral/Int64->Int"    fromIntegral = \(I64# x#) -> I#   (int64ToInt# x#)
486 "fromIntegral/Int64->Word"   fromIntegral = \(I64# x#) -> W#   (int2Word# (int64ToInt# x#))
487 "fromIntegral/Int64->Word64" fromIntegral = \(I64# x#) -> W64# (int64ToWord64# x#)
488 "fromIntegral/Int64->Int64"  fromIntegral = id :: Int64 -> Int64
489     #-}
490
491 #else
492
493 data Int64 = I64# Int# deriving (Eq, Ord)
494
495 instance Show Int64 where
496     showsPrec p x = showsPrec p (fromIntegral x :: Int)
497
498 instance Num Int64 where
499     (I64# x#) + (I64# y#)  = I64# (x# +# y#)
500     (I64# x#) - (I64# y#)  = I64# (x# -# y#)
501     (I64# x#) * (I64# y#)  = I64# (x# *# y#)
502     negate (I64# x#)       = I64# (negateInt# x#)
503     abs x | x >= 0         = x
504           | otherwise      = negate x
505     signum x | x > 0       = 1
506     signum 0               = 0
507     signum _               = -1
508     fromInteger (S# i#)    = I64# i#
509     fromInteger (J# s# d#) = I64# (integer2Int# s# d#)
510
511 instance Enum Int64 where
512     succ x
513         | x /= maxBound = x + 1
514         | otherwise     = succError "Int64"
515     pred x
516         | x /= minBound = x - 1
517         | otherwise     = predError "Int64"
518     toEnum (I# i#)      = I64# i#
519     fromEnum (I64# x#)  = I# x#
520     enumFrom            = boundedEnumFrom
521     enumFromThen        = boundedEnumFromThen
522
523 instance Integral Int64 where
524     quot    x@(I64# x#) y@(I64# y#)
525         | y /= 0                  = I64# (x# `quotInt#` y#)
526         | otherwise               = divZeroError "quot{Int64}" x
527     rem     x@(I64# x#) y@(I64# y#)
528         | y /= 0                  = I64# (x# `remInt#` y#)
529         | otherwise               = divZeroError "rem{Int64}" x
530     div     x@(I64# x#) y@(I64# y#)
531         | y /= 0                  = I64# (x# `divInt#` y#)
532         | otherwise               = divZeroError "div{Int64}" x
533     mod     x@(I64# x#) y@(I64# y#)
534         | y /= 0                  = I64# (x# `modInt#` y#)
535         | otherwise               = divZeroError "mod{Int64}" x
536     quotRem x@(I64# x#) y@(I64# y#)
537         | y /= 0                  = (I64# (x# `quotInt#` y#), I64# (x# `remInt#` y#))
538         | otherwise               = divZeroError "quotRem{Int64}" x
539     divMod  x@(I64# x#) y@(I64# y#)
540         | y /= 0                  = (I64# (x# `divInt#` y#), I64# (x# `modInt#` y#))
541         | otherwise               = divZeroError "divMod{Int64}" x
542     toInteger (I64# x#)           = S# x#
543
544 instance Read Int64 where
545     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
546
547 instance Bits Int64 where
548     (I64# x#) .&.   (I64# y#)  = I64# (word2Int# (int2Word# x# `and#` int2Word# y#))
549     (I64# x#) .|.   (I64# y#)  = I64# (word2Int# (int2Word# x# `or#`  int2Word# y#))
550     (I64# x#) `xor` (I64# y#)  = I64# (word2Int# (int2Word# x# `xor#` int2Word# y#))
551     complement (I64# x#)       = I64# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
552     (I64# x#) `shift` (I# i#)
553         | i# >=# 0#            = I64# (x# `iShiftL#` i#)
554         | otherwise            = I64# (x# `iShiftRA#` negateInt# i#)
555     (I64# x#) `rotate` (I# i#) =
556         I64# (word2Int# ((x'# `shiftL#` i'#) `or#`
557                          (x'# `shiftRL#` (64# -# i'#))))
558         where
559         x'# = int2Word# x#
560         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
561     bitSize  _                 = 64
562     isSigned _                 = True
563
564 {-# RULES
565 "fromIntegral/a->Int64" fromIntegral = \x -> case fromIntegral x of I# x# -> I64# (intToInt64# x#)
566 "fromIntegral/Int64->a" fromIntegral = \(I64# x#) -> fromIntegral (I# x#)
567     #-}
568
569 #endif
570
571 instance CCallable Int64
572 instance CReturnable Int64
573
574 instance Real Int64 where
575     toRational x = toInteger x % 1
576
577 instance Bounded Int64 where
578     minBound = -0x8000000000000000
579     maxBound =  0x7FFFFFFFFFFFFFFF
580
581 instance Ix Int64 where
582     range (m,n)       = [m..n]
583     index b@(m,_) i
584         | inRange b i = fromIntegral (i - m)
585         | otherwise   = indexError b i "Int64"
586     inRange (m,n) i   = m <= i && i <= n
587 \end{code}