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