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