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