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