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