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