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