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