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