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