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