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