[project @ 2002-02-12 11:44:54 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 -fno-implicit-prelude #-}
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 import PrelShow
24
25 ------------------------------------------------------------------------
26 -- type Int8
27 ------------------------------------------------------------------------
28
29 -- Int8 is represented in the same way as Int. Operations may assume
30 -- and must ensure that it holds only values from its logical range.
31
32 data Int8 = I8# Int# deriving (Eq, Ord)
33
34 instance CCallable Int8
35 instance CReturnable Int8
36
37 instance Show Int8 where
38     showsPrec p x = showsPrec p (fromIntegral x :: Int)
39
40 instance Num Int8 where
41     (I8# x#) + (I8# y#)    = I8# (narrow8Int# (x# +# y#))
42     (I8# x#) - (I8# y#)    = I8# (narrow8Int# (x# -# y#))
43     (I8# x#) * (I8# y#)    = I8# (narrow8Int# (x# *# y#))
44     negate (I8# x#)        = I8# (narrow8Int# (negateInt# x#))
45     abs x | x >= 0         = x
46           | otherwise      = negate x
47     signum x | x > 0       = 1
48     signum 0               = 0
49     signum _               = -1
50     fromInteger (S# i#)    = I8# (narrow8Int# i#)
51     fromInteger (J# s# d#) = I8# (narrow8Int# (integer2Int# s# d#))
52
53 instance Real Int8 where
54     toRational x = toInteger x % 1
55
56 instance Enum Int8 where
57     succ x
58         | x /= maxBound = x + 1
59         | otherwise     = succError "Int8"
60     pred x
61         | x /= minBound = x - 1
62         | otherwise     = predError "Int8"
63     toEnum i@(I# i#)
64         | i >= fromIntegral (minBound::Int8) && i <= fromIntegral (maxBound::Int8)
65                         = I8# i#
66         | otherwise     = toEnumError "Int8" i (minBound::Int8, maxBound::Int8)
67     fromEnum (I8# x#)   = I# x#
68     enumFrom            = boundedEnumFrom
69     enumFromThen        = boundedEnumFromThen
70
71 instance Integral Int8 where
72     quot    x@(I8# x#) y@(I8# y#)
73         | y /= 0                  = I8# (narrow8Int# (x# `quotInt#` y#))
74         | otherwise               = divZeroError "quot{Int8}" x
75     rem     x@(I8# x#) y@(I8# y#)
76         | y /= 0                  = I8# (narrow8Int# (x# `remInt#` y#))
77         | otherwise               = divZeroError "rem{Int8}" x
78     div     x@(I8# x#) y@(I8# y#)
79         | y /= 0                  = I8# (narrow8Int# (x# `divInt#` y#))
80         | otherwise               = divZeroError "div{Int8}" x
81     mod     x@(I8# x#) y@(I8# y#)
82         | y /= 0                  = I8# (narrow8Int# (x# `modInt#` y#))
83         | otherwise               = divZeroError "mod{Int8}" x
84     quotRem x@(I8# x#) y@(I8# y#)
85         | y /= 0                  = (I8# (narrow8Int# (x# `quotInt#` y#)),
86                                     I8# (narrow8Int# (x# `remInt#` y#)))
87         | otherwise               = divZeroError "quotRem{Int8}" x
88     divMod  x@(I8# x#) y@(I8# y#)
89         | y /= 0                  = (I8# (narrow8Int# (x# `divInt#` y#)),
90                                     I8# (narrow8Int# (x# `modInt#` y#)))
91         | otherwise               = divZeroError "divMod{Int8}" x
92     toInteger (I8# x#)            = S# x#
93
94 instance Bounded Int8 where
95     minBound = -0x80
96     maxBound =  0x7F
97
98 instance Ix Int8 where
99     range (m,n)              = [m..n]
100     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
101     inRange (m,n) i          = m <= i && i <= n
102     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
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# x#
114         | i# >=# 8#     = I8# 0#
115         | i# ># 0#      = I8# (narrow8Int# (x# `uncheckedIShiftL#` i#))
116         | i# <=# -8#    = I8# (if x# <# 0# then -1# else 0#)
117         | otherwise     = I8# (x# `uncheckedIShiftRA#` negateInt# i#)
118     (I8# x#) `rotate` (I# i#)
119         | i'# ==# 0# 
120         = I8# x#
121         | otherwise
122         = I8# (narrow8Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
123                                        (x'# `uncheckedShiftRL#` (8# -# i'#)))))
124         where
125         x'# = narrow8Word# (int2Word# x#)
126         i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
127     bitSize  _                = 8
128     isSigned _                = True
129
130 {-# RULES
131 "fromIntegral/Int8->Int8" fromIntegral = id :: Int8 -> Int8
132 "fromIntegral/a->Int8"    fromIntegral = \x -> case fromIntegral x of I# x# -> I8# (narrow8Int# x#)
133 "fromIntegral/Int8->a"    fromIntegral = \(I8# x#) -> fromIntegral (I# x#)
134   #-}
135
136 ------------------------------------------------------------------------
137 -- type Int16
138 ------------------------------------------------------------------------
139
140 -- Int16 is represented in the same way as Int. Operations may assume
141 -- and must ensure that it holds only values from its logical range.
142
143 data Int16 = I16# Int# deriving (Eq, Ord)
144
145 instance CCallable Int16
146 instance CReturnable Int16
147
148 instance Show Int16 where
149     showsPrec p x = showsPrec p (fromIntegral x :: Int)
150
151 instance Num Int16 where
152     (I16# x#) + (I16# y#)  = I16# (narrow16Int# (x# +# y#))
153     (I16# x#) - (I16# y#)  = I16# (narrow16Int# (x# -# y#))
154     (I16# x#) * (I16# y#)  = I16# (narrow16Int# (x# *# y#))
155     negate (I16# x#)       = I16# (narrow16Int# (negateInt# x#))
156     abs x | x >= 0         = x
157           | otherwise      = negate x
158     signum x | x > 0       = 1
159     signum 0               = 0
160     signum _               = -1
161     fromInteger (S# i#)    = I16# (narrow16Int# i#)
162     fromInteger (J# s# d#) = I16# (narrow16Int# (integer2Int# s# d#))
163
164 instance Real Int16 where
165     toRational x = toInteger x % 1
166
167 instance Enum Int16 where
168     succ x
169         | x /= maxBound = x + 1
170         | otherwise     = succError "Int16"
171     pred x
172         | x /= minBound = x - 1
173         | otherwise     = predError "Int16"
174     toEnum i@(I# i#)
175         | i >= fromIntegral (minBound::Int16) && i <= fromIntegral (maxBound::Int16)
176                         = I16# i#
177         | otherwise     = toEnumError "Int16" i (minBound::Int16, maxBound::Int16)
178     fromEnum (I16# x#)  = I# x#
179     enumFrom            = boundedEnumFrom
180     enumFromThen        = boundedEnumFromThen
181
182 instance Integral Int16 where
183     quot    x@(I16# x#) y@(I16# y#)
184         | y /= 0                  = I16# (narrow16Int# (x# `quotInt#` y#))
185         | otherwise               = divZeroError "quot{Int16}" x
186     rem     x@(I16# x#) y@(I16# y#)
187         | y /= 0                  = I16# (narrow16Int# (x# `remInt#` y#))
188         | otherwise               = divZeroError "rem{Int16}" x
189     div     x@(I16# x#) y@(I16# y#)
190         | y /= 0                  = I16# (narrow16Int# (x# `divInt#` y#))
191         | otherwise               = divZeroError "div{Int16}" x
192     mod     x@(I16# x#) y@(I16# y#)
193         | y /= 0                  = I16# (narrow16Int# (x# `modInt#` y#))
194         | otherwise               = divZeroError "mod{Int16}" x
195     quotRem x@(I16# x#) y@(I16# y#)
196         | y /= 0                  = (I16# (narrow16Int# (x# `quotInt#` y#)),
197                                     I16# (narrow16Int# (x# `remInt#` y#)))
198         | otherwise               = divZeroError "quotRem{Int16}" x
199     divMod  x@(I16# x#) y@(I16# y#)
200         | y /= 0                  = (I16# (narrow16Int# (x# `divInt#` y#)),
201                                     I16# (narrow16Int# (x# `modInt#` y#)))
202         | otherwise               = divZeroError "divMod{Int16}" x
203     toInteger (I16# x#)           = S# x#
204
205 instance Bounded Int16 where
206     minBound = -0x8000
207     maxBound =  0x7FFF
208
209 instance Ix Int16 where
210     range (m,n)              = [m..n]
211     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
212     inRange (m,n) i          = m <= i && i <= n
213     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
214
215 instance Read Int16 where
216     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
217
218 instance Bits Int16 where
219     (I16# x#) .&.   (I16# y#)  = I16# (word2Int# (int2Word# x# `and#` int2Word# y#))
220     (I16# x#) .|.   (I16# y#)  = I16# (word2Int# (int2Word# x# `or#`  int2Word# y#))
221     (I16# x#) `xor` (I16# y#)  = I16# (word2Int# (int2Word# x# `xor#` int2Word# y#))
222     complement (I16# x#)       = I16# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
223     (I16# x#) `shift` (I# i#)
224         | i# ==# 0#      = I16# x#
225         | i# >=# 16#     = I16# 0#
226         | i# ># 0#       = I16# (narrow16Int# (x# `uncheckedIShiftL#` i#))
227         | i# <=# -16#    = I16# (if x# <# 0# then -1# else 0#)
228         | otherwise      = I16# (x# `uncheckedIShiftRA#` negateInt# i#)
229     (I16# x#) `rotate` (I# i#)
230         | i'# ==# 0# 
231         = I16# x#
232         | otherwise
233         = I16# (narrow16Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
234                                          (x'# `uncheckedShiftRL#` (16# -# i'#)))))
235         where
236         x'# = narrow16Word# (int2Word# x#)
237         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
238     bitSize  _                 = 16
239     isSigned _                 = True
240
241 {-# RULES
242 "fromIntegral/Word8->Int16"  fromIntegral = \(W8# x#) -> I16# (word2Int# x#)
243 "fromIntegral/Int8->Int16"   fromIntegral = \(I8# x#) -> I16# x#
244 "fromIntegral/Int16->Int16"  fromIntegral = id :: Int16 -> Int16
245 "fromIntegral/a->Int16"      fromIntegral = \x -> case fromIntegral x of I# x# -> I16# (narrow16Int# x#)
246 "fromIntegral/Int16->a"      fromIntegral = \(I16# x#) -> fromIntegral (I# x#)
247   #-}
248
249 ------------------------------------------------------------------------
250 -- type Int32
251 ------------------------------------------------------------------------
252
253 #if WORD_SIZE_IN_BITS < 32
254
255 data Int32 = I32# Int32#
256
257 instance Eq Int32 where
258     (I32# x#) == (I32# y#) = x# `eqInt32#` y#
259     (I32# x#) /= (I32# y#) = x# `neInt32#` y#
260
261 instance Ord Int32 where
262     (I32# x#) <  (I32# y#) = x# `ltInt32#` y#
263     (I32# x#) <= (I32# y#) = x# `leInt32#` y#
264     (I32# x#) >  (I32# y#) = x# `gtInt32#` y#
265     (I32# x#) >= (I32# y#) = x# `geInt32#` y#
266
267 instance Show Int32 where
268     showsPrec p x = showsPrec p (toInteger x)
269
270 instance Num Int32 where
271     (I32# x#) + (I32# y#)  = I32# (x# `plusInt32#`  y#)
272     (I32# x#) - (I32# y#)  = I32# (x# `minusInt32#` y#)
273     (I32# x#) * (I32# y#)  = I32# (x# `timesInt32#` y#)
274     negate (I32# x#)       = I32# (negateInt32# x#)
275     abs x | x >= 0         = x
276           | otherwise      = negate x
277     signum x | x > 0       = 1
278     signum 0               = 0
279     signum _               = -1
280     fromInteger (S# i#)    = I32# (intToInt32# i#)
281     fromInteger (J# s# d#) = I32# (integerToInt32# s# d#)
282
283 instance Enum Int32 where
284     succ x
285         | x /= maxBound = x + 1
286         | otherwise     = succError "Int32"
287     pred x
288         | x /= minBound = x - 1
289         | otherwise     = predError "Int32"
290     toEnum (I# i#)      = I32# (intToInt32# i#)
291     fromEnum x@(I32# x#)
292         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
293                         = I# (int32ToInt# x#)
294         | otherwise     = fromEnumError "Int32" x
295     enumFrom            = integralEnumFrom
296     enumFromThen        = integralEnumFromThen
297     enumFromTo          = integralEnumFromTo
298     enumFromThenTo      = integralEnumFromThenTo
299
300 instance Integral Int32 where
301     quot    x@(I32# x#) y@(I32# y#)
302         | y /= 0                  = I32# (x# `quotInt32#` y#)
303         | otherwise               = divZeroError "quot{Int32}" x
304     rem     x@(I32# x#) y@(I32# y#)
305         | y /= 0                  = I32# (x# `remInt32#` y#)
306         | otherwise               = divZeroError "rem{Int32}" x
307     div     x@(I32# x#) y@(I32# y#)
308         | y /= 0                  = I32# (x# `divInt32#` y#)
309         | otherwise               = divZeroError "div{Int32}" x
310     mod     x@(I32# x#) y@(I32# y#)
311         | y /= 0                  = I32# (x# `modInt32#` y#)
312         | otherwise               = divZeroError "mod{Int32}" x
313     quotRem x@(I32# x#) y@(I32# y#)
314         | y /= 0                  = (I32# (x# `quotInt32#` y#), I32# (x# `remInt32#` y#))
315         | otherwise               = divZeroError "quotRem{Int32}" x
316     divMod  x@(I32# x#) y@(I32# y#)
317         | y /= 0                  = (I32# (x# `divInt32#` y#), I32# (x# `modInt32#` y#))
318         | otherwise               = divZeroError "divMod{Int32}" x
319     toInteger x@(I32# x#)
320         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
321                                   = S# (int32ToInt# x#)
322         | otherwise               = case int32ToInteger# x# of (# s, d #) -> J# s d
323
324 divInt32#, modInt32# :: Int32# -> Int32# -> Int32#
325 x# `divInt32#` y#
326     | (x# `gtInt32#` intToInt32# 0#) && (y# `ltInt32#` intToInt32# 0#)
327         = ((x# `minusInt32#` y#) `minusInt32#` intToInt32# 1#) `quotInt32#` y#
328     | (x# `ltInt32#` intToInt32# 0#) && (y# `gtInt32#` intToInt32# 0#)
329         = ((x# `minusInt32#` y#) `plusInt32#` intToInt32# 1#) `quotInt32#` y#
330     | otherwise                = x# `quotInt32#` y#
331 x# `modInt32#` y#
332     | (x# `gtInt32#` intToInt32# 0#) && (y# `ltInt32#` intToInt32# 0#) ||
333       (x# `ltInt32#` intToInt32# 0#) && (y# `gtInt32#` intToInt32# 0#)
334         = if r# `neInt32#` intToInt32# 0# then r# `plusInt32#` y# else intToInt32# 0#
335     | otherwise = r#
336     where
337     r# = x# `remInt32#` y#
338
339 instance Read Int32 where
340     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
341
342 instance Bits Int32 where
343     (I32# x#) .&.   (I32# y#)  = I32# (word32ToInt32# (int32ToWord32# x# `and32#` int32ToWord32# y#))
344     (I32# x#) .|.   (I32# y#)  = I32# (word32ToInt32# (int32ToWord32# x# `or32#`  int32ToWord32# y#))
345     (I32# x#) `xor` (I32# y#)  = I32# (word32ToInt32# (int32ToWord32# x# `xor32#` int32ToWord32# y#))
346     complement (I32# x#)       = I32# (word32ToInt32# (not32# (int32ToWord32# x#)))
347     (I32# x#) `shift` (I# i#)
348         | i# ==# 0#      = I32# x#
349         | i# >=# 32#     = I32# 0#
350         | i# ># 0#       = I32# (x# `uncheckedIShiftL32#` i#)
351         | i# <=# -32#    = I32# (if x# <# 0# then -1# else 0#)
352         | otherwise      = I32# (x# `uncheckedIShiftRA32#` negateInt# i#)
353     (I32# x#) `rotate` (I# i#)
354         | i'# ==# 0# 
355         = I32# x#
356         | otherwise
357         = I32# (word32ToInt32# ((x'# `uncheckedShiftL32#` i'#) `or32#`
358                                 (x'# `uncheckedShiftRL32#` (32# -# i'#))))
359         where
360         x'# = int32ToWord32# x#
361         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
362     bitSize  _                 = 32
363     isSigned _                 = True
364
365 foreign import "stg_eqInt32"       unsafe eqInt32#       :: Int32# -> Int32# -> Bool
366 foreign import "stg_neInt32"       unsafe neInt32#       :: Int32# -> Int32# -> Bool
367 foreign import "stg_ltInt32"       unsafe ltInt32#       :: Int32# -> Int32# -> Bool
368 foreign import "stg_leInt32"       unsafe leInt32#       :: Int32# -> Int32# -> Bool
369 foreign import "stg_gtInt32"       unsafe gtInt32#       :: Int32# -> Int32# -> Bool
370 foreign import "stg_geInt32"       unsafe geInt32#       :: Int32# -> Int32# -> Bool
371 foreign import "stg_plusInt32"     unsafe plusInt32#     :: Int32# -> Int32# -> Int32#
372 foreign import "stg_minusInt32"    unsafe minusInt32#    :: Int32# -> Int32# -> Int32#
373 foreign import "stg_timesInt32"    unsafe timesInt32#    :: Int32# -> Int32# -> Int32#
374 foreign import "stg_negateInt32"   unsafe negateInt32#   :: Int32# -> Int32#
375 foreign import "stg_quotInt32"     unsafe quotInt32#     :: Int32# -> Int32# -> Int32#
376 foreign import "stg_remInt32"      unsafe remInt32#      :: Int32# -> Int32# -> Int32#
377 foreign import "stg_intToInt32"    unsafe intToInt32#    :: Int# -> Int32#
378 foreign import "stg_int32ToInt"    unsafe int32ToInt#    :: Int32# -> Int#
379 foreign import "stg_wordToWord32"  unsafe wordToWord32#  :: Word# -> Word32#
380 foreign import "stg_int32ToWord32" unsafe int32ToWord32# :: Int32# -> Word32#
381 foreign import "stg_word32ToInt32" unsafe word32ToInt32# :: Word32# -> Int32#
382 foreign import "stg_and32"         unsafe and32#         :: Word32# -> Word32# -> Word32#
383 foreign import "stg_or32"          unsafe or32#          :: Word32# -> Word32# -> Word32#
384 foreign import "stg_xor32"         unsafe xor32#         :: Word32# -> Word32# -> Word32#
385 foreign import "stg_not32"         unsafe not32#         :: Word32# -> Word32#
386 foreign import "stg_uncheckedIShiftL32"     unsafe uncheckedIShiftL32#  :: Int32# -> Int# -> Int32#
387 foreign import "stg_uncheckedIShiftRA32"    unsafe uncheckedIShiftRA32# :: Int32# -> Int# -> Int32#
388 foreign import "stg_uncheckedShiftL32"      unsafe uncheckedShiftL32#   :: Word32# -> Int# -> Word32#
389 foreign import "stg_uncheckedShiftRL32"     unsafe uncheckedShiftRL32#  :: Word32# -> Int# -> Word32#
390
391 {-# RULES
392 "fromIntegral/Int->Int32"    fromIntegral = \(I#   x#) -> I32# (intToInt32# x#)
393 "fromIntegral/Word->Int32"   fromIntegral = \(W#   x#) -> I32# (word32ToInt32# (wordToWord32# x#))
394 "fromIntegral/Word32->Int32" fromIntegral = \(W32# x#) -> I32# (word32ToInt32# x#)
395 "fromIntegral/Int32->Int"    fromIntegral = \(I32# x#) -> I#   (int32ToInt# x#)
396 "fromIntegral/Int32->Word"   fromIntegral = \(I32# x#) -> W#   (int2Word# (int32ToInt# x#))
397 "fromIntegral/Int32->Word32" fromIntegral = \(I32# x#) -> W32# (int32ToWord32# x#)
398 "fromIntegral/Int32->Int32"  fromIntegral = id :: Int32 -> Int32
399   #-}
400
401 #else 
402
403 -- Int32 is represented in the same way as Int.
404 #if WORD_SIZE_IN_BITS > 32
405 -- Operations may assume and must ensure that it holds only values
406 -- from its logical range.
407 #endif
408
409 data Int32 = I32# Int# deriving (Eq, Ord)
410
411 instance Show Int32 where
412     showsPrec p x = showsPrec p (fromIntegral x :: Int)
413
414 instance Num Int32 where
415     (I32# x#) + (I32# y#)  = I32# (narrow32Int# (x# +# y#))
416     (I32# x#) - (I32# y#)  = I32# (narrow32Int# (x# -# y#))
417     (I32# x#) * (I32# y#)  = I32# (narrow32Int# (x# *# y#))
418     negate (I32# x#)       = I32# (narrow32Int# (negateInt# x#))
419     abs x | x >= 0         = x
420           | otherwise      = negate x
421     signum x | x > 0       = 1
422     signum 0               = 0
423     signum _               = -1
424     fromInteger (S# i#)    = I32# (narrow32Int# i#)
425     fromInteger (J# s# d#) = I32# (narrow32Int# (integer2Int# s# d#))
426
427 instance Enum Int32 where
428     succ x
429         | x /= maxBound = x + 1
430         | otherwise     = succError "Int32"
431     pred x
432         | x /= minBound = x - 1
433         | otherwise     = predError "Int32"
434 #if WORD_SIZE_IN_BITS == 32
435     toEnum (I# i#)      = I32# i#
436 #else
437     toEnum i@(I# i#)
438         | i >= fromIntegral (minBound::Int32) && i <= fromIntegral (maxBound::Int32)
439                         = I32# i#
440         | otherwise     = toEnumError "Int32" i (minBound::Int32, maxBound::Int32)
441 #endif
442     fromEnum (I32# x#)  = I# x#
443     enumFrom            = boundedEnumFrom
444     enumFromThen        = boundedEnumFromThen
445
446 instance Integral Int32 where
447     quot    x@(I32# x#) y@(I32# y#)
448         | y /= 0                  = I32# (narrow32Int# (x# `quotInt#` y#))
449         | otherwise               = divZeroError "quot{Int32}" x
450     rem     x@(I32# x#) y@(I32# y#)
451         | y /= 0                  = I32# (narrow32Int# (x# `remInt#` y#))
452         | otherwise               = divZeroError "rem{Int32}" x
453     div     x@(I32# x#) y@(I32# y#)
454         | y /= 0                  = I32# (narrow32Int# (x# `divInt#` y#))
455         | otherwise               = divZeroError "div{Int32}" x
456     mod     x@(I32# x#) y@(I32# y#)
457         | y /= 0                  = I32# (narrow32Int# (x# `modInt#` y#))
458         | otherwise               = divZeroError "mod{Int32}" x
459     quotRem x@(I32# x#) y@(I32# y#)
460         | y /= 0                  = (I32# (narrow32Int# (x# `quotInt#` y#)),
461                                     I32# (narrow32Int# (x# `remInt#` y#)))
462         | otherwise               = divZeroError "quotRem{Int32}" x
463     divMod  x@(I32# x#) y@(I32# y#)
464         | y /= 0                  = (I32# (narrow32Int# (x# `divInt#` y#)),
465                                     I32# (narrow32Int# (x# `modInt#` y#)))
466         | otherwise               = divZeroError "divMod{Int32}" x
467     toInteger (I32# x#)           = S# x#
468
469 instance Read Int32 where
470     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
471
472 instance Bits Int32 where
473     (I32# x#) .&.   (I32# y#)  = I32# (word2Int# (int2Word# x# `and#` int2Word# y#))
474     (I32# x#) .|.   (I32# y#)  = I32# (word2Int# (int2Word# x# `or#`  int2Word# y#))
475     (I32# x#) `xor` (I32# y#)  = I32# (word2Int# (int2Word# x# `xor#` int2Word# y#))
476     complement (I32# x#)       = I32# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
477     (I32# x#) `shift` (I# i#)
478         | i# ==# 0#      = I32# x#
479         | i# >=# 32#     = I32# 0#
480         | i# ># 0#       = I32# (narrow32Int# (x# `uncheckedIShiftL#` i#))
481         | i# <=# -32#    = I32# (if x# <# 0# then -1# else 0#)
482         | otherwise      = I32# (x# `uncheckedIShiftRA#` negateInt# i#)
483     (I32# x#) `rotate` (I# i#)
484         | i'# ==# 0# 
485         = I32# x#
486         | otherwise
487         = I32# (narrow32Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
488                                         (x'# `uncheckedShiftRL#` (32# -# i'#)))))
489         where
490         x'# = narrow32Word# (int2Word# x#)
491         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
492     bitSize  _                 = 32
493     isSigned _                 = True
494
495 {-# RULES
496 "fromIntegral/Word8->Int32"  fromIntegral = \(W8# x#) -> I32# (word2Int# x#)
497 "fromIntegral/Word16->Int32" fromIntegral = \(W16# x#) -> I32# (word2Int# x#)
498 "fromIntegral/Int8->Int32"   fromIntegral = \(I8# x#) -> I32# x#
499 "fromIntegral/Int16->Int32"  fromIntegral = \(I16# x#) -> I32# x#
500 "fromIntegral/Int32->Int32"  fromIntegral = id :: Int32 -> Int32
501 "fromIntegral/a->Int32"      fromIntegral = \x -> case fromIntegral x of I# x# -> I32# (narrow32Int# x#)
502 "fromIntegral/Int32->a"      fromIntegral = \(I32# x#) -> fromIntegral (I# x#)
503   #-}
504
505 #endif 
506
507 instance CCallable Int32
508 instance CReturnable Int32
509
510 instance Real Int32 where
511     toRational x = toInteger x % 1
512
513 instance Bounded Int32 where
514     minBound = -0x80000000
515     maxBound =  0x7FFFFFFF
516
517 instance Ix Int32 where
518     range (m,n)              = [m..n]
519     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
520     inRange (m,n) i          = m <= i && i <= n
521     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
522
523 ------------------------------------------------------------------------
524 -- type Int64
525 ------------------------------------------------------------------------
526
527 #if WORD_SIZE_IN_BITS < 64
528
529 data Int64 = I64# Int64#
530
531 instance Eq Int64 where
532     (I64# x#) == (I64# y#) = x# `eqInt64#` y#
533     (I64# x#) /= (I64# y#) = x# `neInt64#` y#
534
535 instance Ord Int64 where
536     (I64# x#) <  (I64# y#) = x# `ltInt64#` y#
537     (I64# x#) <= (I64# y#) = x# `leInt64#` y#
538     (I64# x#) >  (I64# y#) = x# `gtInt64#` y#
539     (I64# x#) >= (I64# y#) = x# `geInt64#` y#
540
541 instance Show Int64 where
542     showsPrec p x = showsPrec p (toInteger x)
543
544 instance Num Int64 where
545     (I64# x#) + (I64# y#)  = I64# (x# `plusInt64#`  y#)
546     (I64# x#) - (I64# y#)  = I64# (x# `minusInt64#` y#)
547     (I64# x#) * (I64# y#)  = I64# (x# `timesInt64#` y#)
548     negate (I64# x#)       = I64# (negateInt64# x#)
549     abs x | x >= 0         = x
550           | otherwise      = negate x
551     signum x | x > 0       = 1
552     signum 0               = 0
553     signum _               = -1
554     fromInteger (S# i#)    = I64# (intToInt64# i#)
555     fromInteger (J# s# d#) = I64# (integerToInt64# s# d#)
556
557 instance Enum Int64 where
558     succ x
559         | x /= maxBound = x + 1
560         | otherwise     = succError "Int64"
561     pred x
562         | x /= minBound = x - 1
563         | otherwise     = predError "Int64"
564     toEnum (I# i#)      = I64# (intToInt64# i#)
565     fromEnum x@(I64# x#)
566         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
567                         = I# (int64ToInt# x#)
568         | otherwise     = fromEnumError "Int64" x
569     enumFrom            = integralEnumFrom
570     enumFromThen        = integralEnumFromThen
571     enumFromTo          = integralEnumFromTo
572     enumFromThenTo      = integralEnumFromThenTo
573
574 instance Integral Int64 where
575     quot    x@(I64# x#) y@(I64# y#)
576         | y /= 0                  = I64# (x# `quotInt64#` y#)
577         | otherwise               = divZeroError "quot{Int64}" x
578     rem     x@(I64# x#) y@(I64# y#)
579         | y /= 0                  = I64# (x# `remInt64#` y#)
580         | otherwise               = divZeroError "rem{Int64}" x
581     div     x@(I64# x#) y@(I64# y#)
582         | y /= 0                  = I64# (x# `divInt64#` y#)
583         | otherwise               = divZeroError "div{Int64}" x
584     mod     x@(I64# x#) y@(I64# y#)
585         | y /= 0                  = I64# (x# `modInt64#` y#)
586         | otherwise               = divZeroError "mod{Int64}" x
587     quotRem x@(I64# x#) y@(I64# y#)
588         | y /= 0                  = (I64# (x# `quotInt64#` y#), I64# (x# `remInt64#` y#))
589         | otherwise               = divZeroError "quotRem{Int64}" x
590     divMod  x@(I64# x#) y@(I64# y#)
591         | y /= 0                  = (I64# (x# `divInt64#` y#), I64# (x# `modInt64#` y#))
592         | otherwise               = divZeroError "divMod{Int64}" x
593     toInteger x@(I64# x#)
594         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
595                                   = S# (int64ToInt# x#)
596         | otherwise               = case int64ToInteger# x# of (# s, d #) -> J# s d
597
598
599 divInt64#, modInt64# :: Int64# -> Int64# -> Int64#
600 x# `divInt64#` y#
601     | (x# `gtInt64#` intToInt64# 0#) && (y# `ltInt64#` intToInt64# 0#)
602         = ((x# `minusInt64#` y#) `minusInt64#` intToInt64# 1#) `quotInt64#` y#
603     | (x# `ltInt64#` intToInt64# 0#) && (y# `gtInt64#` intToInt64# 0#)
604         = ((x# `minusInt64#` y#) `plusInt64#` intToInt64# 1#) `quotInt64#` y#
605     | otherwise                = x# `quotInt64#` y#
606 x# `modInt64#` y#
607     | (x# `gtInt64#` intToInt64# 0#) && (y# `ltInt64#` intToInt64# 0#) ||
608       (x# `ltInt64#` intToInt64# 0#) && (y# `gtInt64#` intToInt64# 0#)
609         = if r# `neInt64#` intToInt64# 0# then r# `plusInt64#` y# else intToInt64# 0#
610     | otherwise = r#
611     where
612     r# = x# `remInt64#` y#
613
614 instance Read Int64 where
615     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
616
617 instance Bits Int64 where
618     (I64# x#) .&.   (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `and64#` int64ToWord64# y#))
619     (I64# x#) .|.   (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `or64#`  int64ToWord64# y#))
620     (I64# x#) `xor` (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `xor64#` int64ToWord64# y#))
621     complement (I64# x#)       = I64# (word64ToInt64# (not64# (int64ToWord64# x#)))
622     (I64# x#) `shift` (I# i#)
623         | i# ==# 0#      = I64# x#
624         | i# >=# 64#     = 0
625         | i# ># 0#       = I64# (x# `uncheckedIShiftL64#` i#)
626         | i# <=# -64#    = if (I64# x#) < 0 then -1 else 0
627         | otherwise      = I64# (x# `uncheckedIShiftRA64#` negateInt# i#)
628     (I64# x#) `rotate` (I# i#)
629         | i'# ==# 0# 
630         = I64# x#
631         | otherwise
632         = I64# (word64ToInt64# ((x'# `uncheckedShiftL64#` i'#) `or64#`
633                                 (x'# `uncheckedShiftRL64#` (64# -# i'#))))
634         where
635         x'# = int64ToWord64# x#
636         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
637     bitSize  _                 = 64
638     isSigned _                 = True
639
640 foreign import "stg_eqInt64"       unsafe eqInt64#       :: Int64# -> Int64# -> Bool
641 foreign import "stg_neInt64"       unsafe neInt64#       :: Int64# -> Int64# -> Bool
642 foreign import "stg_ltInt64"       unsafe ltInt64#       :: Int64# -> Int64# -> Bool
643 foreign import "stg_leInt64"       unsafe leInt64#       :: Int64# -> Int64# -> Bool
644 foreign import "stg_gtInt64"       unsafe gtInt64#       :: Int64# -> Int64# -> Bool
645 foreign import "stg_geInt64"       unsafe geInt64#       :: Int64# -> Int64# -> Bool
646 foreign import "stg_plusInt64"     unsafe plusInt64#     :: Int64# -> Int64# -> Int64#
647 foreign import "stg_minusInt64"    unsafe minusInt64#    :: Int64# -> Int64# -> Int64#
648 foreign import "stg_timesInt64"    unsafe timesInt64#    :: Int64# -> Int64# -> Int64#
649 foreign import "stg_negateInt64"   unsafe negateInt64#   :: Int64# -> Int64#
650 foreign import "stg_quotInt64"     unsafe quotInt64#     :: Int64# -> Int64# -> Int64#
651 foreign import "stg_remInt64"      unsafe remInt64#      :: Int64# -> Int64# -> Int64#
652 foreign import "stg_intToInt64"    unsafe intToInt64#    :: Int# -> Int64#
653 foreign import "stg_int64ToInt"    unsafe int64ToInt#    :: Int64# -> Int#
654 foreign import "stg_wordToWord64"  unsafe wordToWord64#  :: Word# -> Word64#
655 foreign import "stg_int64ToWord64" unsafe int64ToWord64# :: Int64# -> Word64#
656 foreign import "stg_word64ToInt64" unsafe word64ToInt64# :: Word64# -> Int64#
657 foreign import "stg_and64"         unsafe and64#         :: Word64# -> Word64# -> Word64#
658 foreign import "stg_or64"          unsafe or64#          :: Word64# -> Word64# -> Word64#
659 foreign import "stg_xor64"         unsafe xor64#         :: Word64# -> Word64# -> Word64#
660 foreign import "stg_not64"         unsafe not64#         :: Word64# -> Word64#
661 foreign import "stg_uncheckedIShiftL64"  unsafe uncheckedIShiftL64#  :: Int64# -> Int# -> Int64#
662 foreign import "stg_uncheckedIShiftRA64" unsafe uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
663 foreign import "stg_uncheckedShiftL64"   unsafe uncheckedShiftL64#   :: Word64# -> Int# -> Word64#
664 foreign import "stg_uncheckedShiftRL64"  unsafe uncheckedShiftRL64#  :: Word64# -> Int# -> Word64#
665
666 foreign import "stg_integerToInt64"  unsafe integerToInt64#  :: Int# -> ByteArray# -> Int64#
667
668 {-# RULES
669 "fromIntegral/Int->Int64"    fromIntegral = \(I#   x#) -> I64# (intToInt64# x#)
670 "fromIntegral/Word->Int64"   fromIntegral = \(W#   x#) -> I64# (word64ToInt64# (wordToWord64# x#))
671 "fromIntegral/Word64->Int64" fromIntegral = \(W64# x#) -> I64# (word64ToInt64# x#)
672 "fromIntegral/Int64->Int"    fromIntegral = \(I64# x#) -> I#   (int64ToInt# x#)
673 "fromIntegral/Int64->Word"   fromIntegral = \(I64# x#) -> W#   (int2Word# (int64ToInt# x#))
674 "fromIntegral/Int64->Word64" fromIntegral = \(I64# x#) -> W64# (int64ToWord64# x#)
675 "fromIntegral/Int64->Int64"  fromIntegral = id :: Int64 -> Int64
676   #-}
677
678 #else 
679
680 -- Int64 is represented in the same way as Int.
681 -- Operations may assume and must ensure that it holds only values
682 -- from its logical range.
683
684 data Int64 = I64# Int# deriving (Eq, Ord)
685
686 instance Show Int64 where
687     showsPrec p x = showsPrec p (fromIntegral x :: Int)
688
689 instance Num Int64 where
690     (I64# x#) + (I64# y#)  = I64# (x# +# y#)
691     (I64# x#) - (I64# y#)  = I64# (x# -# y#)
692     (I64# x#) * (I64# y#)  = I64# (x# *# y#)
693     negate (I64# x#)       = I64# (negateInt# x#)
694     abs x | x >= 0         = x
695           | otherwise      = negate x
696     signum x | x > 0       = 1
697     signum 0               = 0
698     signum _               = -1
699     fromInteger (S# i#)    = I64# i#
700     fromInteger (J# s# d#) = I64# (integer2Int# s# d#)
701
702 instance Enum Int64 where
703     succ x
704         | x /= maxBound = x + 1
705         | otherwise     = succError "Int64"
706     pred x
707         | x /= minBound = x - 1
708         | otherwise     = predError "Int64"
709     toEnum (I# i#)      = I64# i#
710     fromEnum (I64# x#)  = I# x#
711     enumFrom            = boundedEnumFrom
712     enumFromThen        = boundedEnumFromThen
713
714 instance Integral Int64 where
715     quot    x@(I64# x#) y@(I64# y#)
716         | y /= 0                  = I64# (x# `quotInt#` y#)
717         | otherwise               = divZeroError "quot{Int64}" x
718     rem     x@(I64# x#) y@(I64# y#)
719         | y /= 0                  = I64# (x# `remInt#` y#)
720         | otherwise               = divZeroError "rem{Int64}" x
721     div     x@(I64# x#) y@(I64# y#)
722         | y /= 0                  = I64# (x# `divInt#` y#)
723         | otherwise               = divZeroError "div{Int64}" x
724     mod     x@(I64# x#) y@(I64# y#)
725         | y /= 0                  = I64# (x# `modInt#` y#)
726         | otherwise               = divZeroError "mod{Int64}" x
727     quotRem x@(I64# x#) y@(I64# y#)
728         | y /= 0                  = (I64# (x# `quotInt#` y#), I64# (x# `remInt#` y#))
729         | otherwise               = divZeroError "quotRem{Int64}" x
730     divMod  x@(I64# x#) y@(I64# y#)
731         | y /= 0                  = (I64# (x# `divInt#` y#), I64# (x# `modInt#` y#))
732         | otherwise               = divZeroError "divMod{Int64}" x
733     toInteger (I64# x#)           = S# x#
734
735 instance Read Int64 where
736     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
737
738 instance Bits Int64 where
739     (I64# x#) .&.   (I64# y#)  = I64# (word2Int# (int2Word# x# `and#` int2Word# y#))
740     (I64# x#) .|.   (I64# y#)  = I64# (word2Int# (int2Word# x# `or#`  int2Word# y#))
741     (I64# x#) `xor` (I64# y#)  = I64# (word2Int# (int2Word# x# `xor#` int2Word# y#))
742     complement (I64# x#)       = I64# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
743     (I64# x#) `shift` (I# i#)
744         | i# ==# 0#      = I64# x#
745         | i# >=# 64#     = 0
746         | i# ># 0#       = I64# (x# `uncheckedIShiftL#` i#)
747         | i# <=# -64#    = if x# <# 0# then -1 else 0
748         | otherwise      = I64# (x# `uncheckedIShiftRA#` negateInt# i#)
749     (I64# x#) `rotate` (I# i#)
750         | i'# ==# 0# 
751         = I64# x#
752         | otherwise
753         = I64# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
754                            (x'# `uncheckedShiftRL#` (64# -# i'#))))
755         where
756         x'# = int2Word# x#
757         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
758     bitSize  _                 = 64
759     isSigned _                 = True
760
761 {-# RULES
762 "fromIntegral/a->Int64" fromIntegral = \x -> case fromIntegral x of I# x# -> I64# x#
763 "fromIntegral/Int64->a" fromIntegral = \(I64# x#) -> fromIntegral (I# x#)
764   #-}
765
766 #endif
767
768 instance CCallable Int64
769 instance CReturnable Int64
770
771 instance Real Int64 where
772     toRational x = toInteger x % 1
773
774 instance Bounded Int64 where
775     minBound = -0x8000000000000000
776     maxBound =  0x7FFFFFFFFFFFFFFF
777
778 instance Ix Int64 where
779     range (m,n)              = [m..n]
780     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
781     inRange (m,n) i          = m <= i && i <= n
782     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
783 \end{code}