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