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