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