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