add Data.Sequence to nhc98 build
[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                  = I8# (narrow8Int# (x# `quotInt#` y#))
82         | otherwise               = divZeroError
83     rem     x@(I8# x#) y@(I8# y#)
84         | y /= 0                  = I8# (narrow8Int# (x# `remInt#` y#))
85         | otherwise               = divZeroError
86     div     x@(I8# x#) y@(I8# y#)
87         | y /= 0                  = I8# (narrow8Int# (x# `divInt#` y#))
88         | otherwise               = divZeroError
89     mod     x@(I8# x#) y@(I8# y#)
90         | y /= 0                  = I8# (narrow8Int# (x# `modInt#` y#))
91         | otherwise               = divZeroError
92     quotRem x@(I8# x#) y@(I8# y#)
93         | y /= 0                  = (I8# (narrow8Int# (x# `quotInt#` y#)),
94                                     I8# (narrow8Int# (x# `remInt#` y#)))
95         | otherwise               = divZeroError
96     divMod  x@(I8# x#) y@(I8# y#)
97         | y /= 0                  = (I8# (narrow8Int# (x# `divInt#` y#)),
98                                     I8# (narrow8Int# (x# `modInt#` y#)))
99         | otherwise               = divZeroError
100     toInteger (I8# x#)            = S# x#
101
102 instance Bounded Int8 where
103     minBound = -0x80
104     maxBound =  0x7F
105
106 instance Ix Int8 where
107     range (m,n)              = [m..n]
108     unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
109     inRange (m,n) i          = m <= i && i <= n
110
111 instance Read Int8 where
112     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
113
114 instance Bits Int8 where
115     {-# INLINE shift #-}
116
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 Show Int16 where
153     showsPrec p x = showsPrec p (fromIntegral x :: Int)
154
155 instance Num Int16 where
156     (I16# x#) + (I16# y#)  = I16# (narrow16Int# (x# +# y#))
157     (I16# x#) - (I16# y#)  = I16# (narrow16Int# (x# -# y#))
158     (I16# x#) * (I16# y#)  = I16# (narrow16Int# (x# *# y#))
159     negate (I16# x#)       = I16# (narrow16Int# (negateInt# x#))
160     abs x | x >= 0         = x
161           | otherwise      = negate x
162     signum x | x > 0       = 1
163     signum 0               = 0
164     signum _               = -1
165     fromInteger (S# i#)    = I16# (narrow16Int# i#)
166     fromInteger (J# s# d#) = I16# (narrow16Int# (integer2Int# s# d#))
167
168 instance Real Int16 where
169     toRational x = toInteger x % 1
170
171 instance Enum Int16 where
172     succ x
173         | x /= maxBound = x + 1
174         | otherwise     = succError "Int16"
175     pred x
176         | x /= minBound = x - 1
177         | otherwise     = predError "Int16"
178     toEnum i@(I# i#)
179         | i >= fromIntegral (minBound::Int16) && i <= fromIntegral (maxBound::Int16)
180                         = I16# i#
181         | otherwise     = toEnumError "Int16" i (minBound::Int16, maxBound::Int16)
182     fromEnum (I16# x#)  = I# x#
183     enumFrom            = boundedEnumFrom
184     enumFromThen        = boundedEnumFromThen
185
186 instance Integral Int16 where
187     quot    x@(I16# x#) y@(I16# y#)
188         | y /= 0                  = I16# (narrow16Int# (x# `quotInt#` y#))
189         | otherwise               = divZeroError
190     rem     x@(I16# x#) y@(I16# y#)
191         | y /= 0                  = I16# (narrow16Int# (x# `remInt#` y#))
192         | otherwise               = divZeroError
193     div     x@(I16# x#) y@(I16# y#)
194         | y /= 0                  = I16# (narrow16Int# (x# `divInt#` y#))
195         | otherwise               = divZeroError
196     mod     x@(I16# x#) y@(I16# y#)
197         | y /= 0                  = I16# (narrow16Int# (x# `modInt#` y#))
198         | otherwise               = divZeroError
199     quotRem x@(I16# x#) y@(I16# y#)
200         | y /= 0                  = (I16# (narrow16Int# (x# `quotInt#` y#)),
201                                     I16# (narrow16Int# (x# `remInt#` y#)))
202         | otherwise               = divZeroError
203     divMod  x@(I16# x#) y@(I16# y#)
204         | y /= 0                  = (I16# (narrow16Int# (x# `divInt#` y#)),
205                                     I16# (narrow16Int# (x# `modInt#` y#)))
206         | otherwise               = divZeroError
207     toInteger (I16# x#)           = S# x#
208
209 instance Bounded Int16 where
210     minBound = -0x8000
211     maxBound =  0x7FFF
212
213 instance Ix Int16 where
214     range (m,n)              = [m..n]
215     unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
216     inRange (m,n) i          = m <= i && i <= n
217
218 instance Read Int16 where
219     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
220
221 instance Bits Int16 where
222     {-# INLINE shift #-}
223
224     (I16# x#) .&.   (I16# y#)  = I16# (word2Int# (int2Word# x# `and#` int2Word# y#))
225     (I16# x#) .|.   (I16# y#)  = I16# (word2Int# (int2Word# x# `or#`  int2Word# y#))
226     (I16# x#) `xor` (I16# y#)  = I16# (word2Int# (int2Word# x# `xor#` int2Word# y#))
227     complement (I16# x#)       = I16# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
228     (I16# x#) `shift` (I# i#)
229         | i# >=# 0#            = I16# (narrow16Int# (x# `iShiftL#` i#))
230         | otherwise            = I16# (x# `iShiftRA#` negateInt# i#)
231     (I16# x#) `rotate` (I# i#)
232         | i'# ==# 0# 
233         = I16# x#
234         | otherwise
235         = I16# (narrow16Int# (word2Int# ((x'# `shiftL#` i'#) `or#`
236                                          (x'# `shiftRL#` (16# -# i'#)))))
237         where
238         x'# = narrow16Word# (int2Word# x#)
239         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
240     bitSize  _                 = 16
241     isSigned _                 = True
242
243 {-# RULES
244 "fromIntegral/Word8->Int16"  fromIntegral = \(W8# x#) -> I16# (word2Int# x#)
245 "fromIntegral/Int8->Int16"   fromIntegral = \(I8# x#) -> I16# x#
246 "fromIntegral/Int16->Int16"  fromIntegral = id :: Int16 -> Int16
247 "fromIntegral/a->Int16"      fromIntegral = \x -> case fromIntegral x of I# x# -> I16# (narrow16Int# x#)
248 "fromIntegral/Int16->a"      fromIntegral = \(I16# x#) -> fromIntegral (I# x#)
249   #-}
250
251 ------------------------------------------------------------------------
252 -- type Int32
253 ------------------------------------------------------------------------
254
255 #if WORD_SIZE_IN_BITS < 32
256
257 data Int32 = I32# Int32#
258 -- ^ 32-bit signed integer type
259
260 instance Eq Int32 where
261     (I32# x#) == (I32# y#) = x# `eqInt32#` y#
262     (I32# x#) /= (I32# y#) = x# `neInt32#` y#
263
264 instance Ord Int32 where
265     (I32# x#) <  (I32# y#) = x# `ltInt32#` y#
266     (I32# x#) <= (I32# y#) = x# `leInt32#` y#
267     (I32# x#) >  (I32# y#) = x# `gtInt32#` y#
268     (I32# x#) >= (I32# y#) = x# `geInt32#` y#
269
270 instance Show Int32 where
271     showsPrec p x = showsPrec p (toInteger x)
272
273 instance Num Int32 where
274     (I32# x#) + (I32# y#)  = I32# (x# `plusInt32#`  y#)
275     (I32# x#) - (I32# y#)  = I32# (x# `minusInt32#` y#)
276     (I32# x#) * (I32# y#)  = I32# (x# `timesInt32#` y#)
277     negate (I32# x#)       = I32# (negateInt32# x#)
278     abs x | x >= 0         = x
279           | otherwise      = negate x
280     signum x | x > 0       = 1
281     signum 0               = 0
282     signum _               = -1
283     fromInteger (S# i#)    = I32# (intToInt32# i#)
284     fromInteger (J# s# d#) = I32# (integerToInt32# s# d#)
285
286 instance Enum Int32 where
287     succ x
288         | x /= maxBound = x + 1
289         | otherwise     = succError "Int32"
290     pred x
291         | x /= minBound = x - 1
292         | otherwise     = predError "Int32"
293     toEnum (I# i#)      = I32# (intToInt32# i#)
294     fromEnum x@(I32# x#)
295         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
296                         = I# (int32ToInt# x#)
297         | otherwise     = fromEnumError "Int32" x
298     enumFrom            = integralEnumFrom
299     enumFromThen        = integralEnumFromThen
300     enumFromTo          = integralEnumFromTo
301     enumFromThenTo      = integralEnumFromThenTo
302
303 instance Integral Int32 where
304     quot    x@(I32# x#) y@(I32# y#)
305         | y /= 0                  = I32# (x# `quotInt32#` y#)
306         | otherwise               = divZeroError
307     rem     x@(I32# x#) y@(I32# y#)
308         | y /= 0                  = I32# (x# `remInt32#` y#)
309         | otherwise               = divZeroError
310     div     x@(I32# x#) y@(I32# y#)
311         | y /= 0                  = I32# (x# `divInt32#` y#)
312         | otherwise               = divZeroError
313     mod     x@(I32# x#) y@(I32# y#)
314         | y /= 0                  = I32# (x# `modInt32#` y#)
315         | otherwise               = divZeroError
316     quotRem x@(I32# x#) y@(I32# y#)
317         | y /= 0                  = (I32# (x# `quotInt32#` y#), I32# (x# `remInt32#` y#))
318         | otherwise               = divZeroError
319     divMod  x@(I32# x#) y@(I32# y#)
320         | y /= 0                  = (I32# (x# `divInt32#` y#), I32# (x# `modInt32#` y#))
321         | otherwise               = divZeroError
322     toInteger x@(I32# x#)
323         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
324                                   = S# (int32ToInt# x#)
325         | otherwise               = case int32ToInteger# x# of (# s, d #) -> J# s d
326
327 divInt32#, modInt32# :: Int32# -> Int32# -> Int32#
328 x# `divInt32#` y#
329     | (x# `gtInt32#` intToInt32# 0#) && (y# `ltInt32#` intToInt32# 0#)
330         = ((x# `minusInt32#` y#) `minusInt32#` intToInt32# 1#) `quotInt32#` y#
331     | (x# `ltInt32#` intToInt32# 0#) && (y# `gtInt32#` intToInt32# 0#)
332         = ((x# `minusInt32#` y#) `plusInt32#` intToInt32# 1#) `quotInt32#` y#
333     | otherwise                = x# `quotInt32#` y#
334 x# `modInt32#` y#
335     | (x# `gtInt32#` intToInt32# 0#) && (y# `ltInt32#` intToInt32# 0#) ||
336       (x# `ltInt32#` intToInt32# 0#) && (y# `gtInt32#` intToInt32# 0#)
337         = if r# `neInt32#` intToInt32# 0# then r# `plusInt32#` y# else intToInt32# 0#
338     | otherwise = r#
339     where
340     r# = x# `remInt32#` y#
341
342 instance Read Int32 where
343     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
344
345 instance Bits Int32 where
346     {-# INLINE shift #-}
347
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
453     rem     x@(I32# x#) y@(I32# y#)
454         | y /= 0                  = I32# (narrow32Int# (x# `remInt#` y#))
455         | otherwise               = divZeroError
456     div     x@(I32# x#) y@(I32# y#)
457         | y /= 0                  = I32# (narrow32Int# (x# `divInt#` y#))
458         | otherwise               = divZeroError
459     mod     x@(I32# x#) y@(I32# y#)
460         | y /= 0                  = I32# (narrow32Int# (x# `modInt#` y#))
461         | otherwise               = divZeroError
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
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
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     {-# INLINE shift #-}
477
478     (I32# x#) .&.   (I32# y#)  = I32# (word2Int# (int2Word# x# `and#` int2Word# y#))
479     (I32# x#) .|.   (I32# y#)  = I32# (word2Int# (int2Word# x# `or#`  int2Word# y#))
480     (I32# x#) `xor` (I32# y#)  = I32# (word2Int# (int2Word# x# `xor#` int2Word# y#))
481     complement (I32# x#)       = I32# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
482     (I32# x#) `shift` (I# i#)
483         | i# >=# 0#            = I32# (narrow32Int# (x# `iShiftL#` i#))
484         | otherwise            = I32# (x# `iShiftRA#` negateInt# i#)
485     (I32# x#) `rotate` (I# i#)
486         | i'# ==# 0# 
487         = I32# x#
488         | otherwise
489         = I32# (narrow32Int# (word2Int# ((x'# `shiftL#` i'#) `or#`
490                                         (x'# `shiftRL#` (32# -# i'#)))))
491         where
492         x'# = narrow32Word# (int2Word# x#)
493         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
494     bitSize  _                 = 32
495     isSigned _                 = True
496
497 {-# RULES
498 "fromIntegral/Word8->Int32"  fromIntegral = \(W8# x#) -> I32# (word2Int# x#)
499 "fromIntegral/Word16->Int32" fromIntegral = \(W16# x#) -> I32# (word2Int# x#)
500 "fromIntegral/Int8->Int32"   fromIntegral = \(I8# x#) -> I32# x#
501 "fromIntegral/Int16->Int32"  fromIntegral = \(I16# x#) -> I32# x#
502 "fromIntegral/Int32->Int32"  fromIntegral = id :: Int32 -> Int32
503 "fromIntegral/a->Int32"      fromIntegral = \x -> case fromIntegral x of I# x# -> I32# (narrow32Int# x#)
504 "fromIntegral/Int32->a"      fromIntegral = \(I32# x#) -> fromIntegral (I# x#)
505   #-}
506
507 #endif 
508
509 instance Real Int32 where
510     toRational x = toInteger x % 1
511
512 instance Bounded Int32 where
513     minBound = -0x80000000
514     maxBound =  0x7FFFFFFF
515
516 instance Ix Int32 where
517     range (m,n)              = [m..n]
518     unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
519     inRange (m,n) i          = m <= i && i <= n
520
521 ------------------------------------------------------------------------
522 -- type Int64
523 ------------------------------------------------------------------------
524
525 #if WORD_SIZE_IN_BITS < 64
526
527 data Int64 = I64# Int64#
528 -- ^ 64-bit signed integer type
529
530 instance Eq Int64 where
531     (I64# x#) == (I64# y#) = x# `eqInt64#` y#
532     (I64# x#) /= (I64# y#) = x# `neInt64#` y#
533
534 instance Ord Int64 where
535     (I64# x#) <  (I64# y#) = x# `ltInt64#` y#
536     (I64# x#) <= (I64# y#) = x# `leInt64#` y#
537     (I64# x#) >  (I64# y#) = x# `gtInt64#` y#
538     (I64# x#) >= (I64# y#) = x# `geInt64#` y#
539
540 instance Show Int64 where
541     showsPrec p x = showsPrec p (toInteger x)
542
543 instance Num Int64 where
544     (I64# x#) + (I64# y#)  = I64# (x# `plusInt64#`  y#)
545     (I64# x#) - (I64# y#)  = I64# (x# `minusInt64#` y#)
546     (I64# x#) * (I64# y#)  = I64# (x# `timesInt64#` y#)
547     negate (I64# x#)       = I64# (negateInt64# x#)
548     abs x | x >= 0         = x
549           | otherwise      = negate x
550     signum x | x > 0       = 1
551     signum 0               = 0
552     signum _               = -1
553     fromInteger (S# i#)    = I64# (intToInt64# i#)
554     fromInteger (J# s# d#) = I64# (integerToInt64# s# d#)
555
556 instance Enum Int64 where
557     succ x
558         | x /= maxBound = x + 1
559         | otherwise     = succError "Int64"
560     pred x
561         | x /= minBound = x - 1
562         | otherwise     = predError "Int64"
563     toEnum (I# i#)      = I64# (intToInt64# i#)
564     fromEnum x@(I64# x#)
565         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
566                         = I# (int64ToInt# x#)
567         | otherwise     = fromEnumError "Int64" x
568     enumFrom            = integralEnumFrom
569     enumFromThen        = integralEnumFromThen
570     enumFromTo          = integralEnumFromTo
571     enumFromThenTo      = integralEnumFromThenTo
572
573 instance Integral Int64 where
574     quot    x@(I64# x#) y@(I64# y#)
575         | y /= 0                  = I64# (x# `quotInt64#` y#)
576         | otherwise               = divZeroError
577     rem     x@(I64# x#) y@(I64# y#)
578         | y /= 0                  = I64# (x# `remInt64#` y#)
579         | otherwise               = divZeroError
580     div     x@(I64# x#) y@(I64# y#)
581         | y /= 0                  = I64# (x# `divInt64#` y#)
582         | otherwise               = divZeroError
583     mod     x@(I64# x#) y@(I64# y#)
584         | y /= 0                  = I64# (x# `modInt64#` y#)
585         | otherwise               = divZeroError
586     quotRem x@(I64# x#) y@(I64# y#)
587         | y /= 0                  = (I64# (x# `quotInt64#` y#), I64# (x# `remInt64#` y#))
588         | otherwise               = divZeroError
589     divMod  x@(I64# x#) y@(I64# y#)
590         | y /= 0                  = (I64# (x# `divInt64#` y#), I64# (x# `modInt64#` y#))
591         | otherwise               = divZeroError
592     toInteger x@(I64# x#)
593         | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
594                                   = S# (int64ToInt# x#)
595         | otherwise               = case int64ToInteger# x# of (# s, d #) -> J# s d
596
597
598 divInt64#, modInt64# :: Int64# -> Int64# -> Int64#
599 x# `divInt64#` y#
600     | (x# `gtInt64#` intToInt64# 0#) && (y# `ltInt64#` intToInt64# 0#)
601         = ((x# `minusInt64#` y#) `minusInt64#` intToInt64# 1#) `quotInt64#` y#
602     | (x# `ltInt64#` intToInt64# 0#) && (y# `gtInt64#` intToInt64# 0#)
603         = ((x# `minusInt64#` y#) `plusInt64#` intToInt64# 1#) `quotInt64#` y#
604     | otherwise                = x# `quotInt64#` y#
605 x# `modInt64#` y#
606     | (x# `gtInt64#` intToInt64# 0#) && (y# `ltInt64#` intToInt64# 0#) ||
607       (x# `ltInt64#` intToInt64# 0#) && (y# `gtInt64#` intToInt64# 0#)
608         = if r# `neInt64#` intToInt64# 0# then r# `plusInt64#` y# else intToInt64# 0#
609     | otherwise = r#
610     where
611     r# = x# `remInt64#` y#
612
613 instance Read Int64 where
614     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
615
616 instance Bits Int64 where
617     {-# INLINE shift #-}
618
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
734     rem     x@(I64# x#) y@(I64# y#)
735         | y /= 0                  = I64# (x# `remInt#` y#)
736         | otherwise               = divZeroError
737     div     x@(I64# x#) y@(I64# y#)
738         | y /= 0                  = I64# (x# `divInt#` y#)
739         | otherwise               = divZeroError
740     mod     x@(I64# x#) y@(I64# y#)
741         | y /= 0                  = I64# (x# `modInt#` y#)
742         | otherwise               = divZeroError
743     quotRem x@(I64# x#) y@(I64# y#)
744         | y /= 0                  = (I64# (x# `quotInt#` y#), I64# (x# `remInt#` y#))
745         | otherwise               = divZeroError
746     divMod  x@(I64# x#) y@(I64# y#)
747         | y /= 0                  = (I64# (x# `divInt#` y#), I64# (x# `modInt#` y#))
748         | otherwise               = divZeroError
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     {-# INLINE shift #-}
756
757     (I64# x#) .&.   (I64# y#)  = I64# (word2Int# (int2Word# x# `and#` int2Word# y#))
758     (I64# x#) .|.   (I64# y#)  = I64# (word2Int# (int2Word# x# `or#`  int2Word# y#))
759     (I64# x#) `xor` (I64# y#)  = I64# (word2Int# (int2Word# x# `xor#` int2Word# y#))
760     complement (I64# x#)       = I64# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
761     (I64# x#) `shift` (I# i#)
762         | i# >=# 0#            = I64# (x# `iShiftL#` i#)
763         | otherwise            = I64# (x# `iShiftRA#` negateInt# i#)
764     (I64# x#) `rotate` (I# i#)
765         | i'# ==# 0# 
766         = I64# x#
767         | otherwise
768         = I64# (word2Int# ((x'# `shiftL#` i'#) `or#`
769                            (x'# `shiftRL#` (64# -# i'#))))
770         where
771         x'# = int2Word# x#
772         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
773     bitSize  _                 = 64
774     isSigned _                 = True
775
776 {-# RULES
777 "fromIntegral/a->Int64" fromIntegral = \x -> case fromIntegral x of I# x# -> I64# x#
778 "fromIntegral/Int64->a" fromIntegral = \(I64# x#) -> fromIntegral (I# x#)
779   #-}
780
781 #endif
782
783 instance Real Int64 where
784     toRational x = toInteger x % 1
785
786 instance Bounded Int64 where
787     minBound = -0x8000000000000000
788     maxBound =  0x7FFFFFFFFFFFFFFF
789
790 instance Ix Int64 where
791     range (m,n)              = [m..n]
792     unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
793     inRange (m,n) i          = m <= i && i <= n