[project @ 1999-11-26 16:26:32 by simonmar]
[ghc-hetmet.git] / ghc / lib / exts / Int.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1997-1999
3 %
4
5 \section[Int]{Module @Int@}
6
7 This code is largely copied from the Hugs library of the same name,
8 suitably hammered to use unboxed types.
9
10 \begin{code}
11 #include "MachDeps.h"
12
13 module Int
14         ( Int8
15         , Int16
16         , Int32
17         , Int64
18
19         , int8ToInt16   -- :: Int8  -> Int16
20         , int8ToInt32   -- :: Int8  -> Int32
21         , int8ToInt64   -- :: Int8  -> Int64
22
23         , int16ToInt8   -- :: Int16 -> Int8
24         , int16ToInt32  -- :: Int16 -> Int32
25         , int16ToInt64  -- :: Int16 -> Int64
26
27         , int32ToInt8   -- :: Int32 -> Int8
28         , int32ToInt16  -- :: Int32 -> Int16
29         , int32ToInt64  -- :: Int32 -> Int64
30
31         , int64ToInt8   -- :: Int64 -> Int8
32         , int64ToInt16  -- :: Int64 -> Int16
33         , int64ToInt32  -- :: Int64 -> Int32
34
35         , int8ToInt  -- :: Int8  -> Int
36         , int16ToInt -- :: Int16 -> Int
37         , int32ToInt -- :: Int32 -> Int
38         , int64ToInt -- :: Int32 -> Int
39
40         , intToInt8  -- :: Int   -> Int8
41         , intToInt16 -- :: Int   -> Int16
42         , intToInt32 -- :: Int   -> Int32
43         , intToInt64 -- :: Int   -> Int32
44
45         , integerToInt8  -- :: Integer -> Int8
46         , integerToInt16 -- :: Integer -> Int16
47         , integerToInt32 -- :: Integer -> Int32
48         , integerToInt64 -- :: Integer -> Int64
49
50         , int8ToInteger  -- :: Int8    -> Integer
51         , int16ToInteger -- :: Int16   -> Integer
52         , int32ToInteger -- :: Int32   -> Integer
53         , int64ToInteger -- :: Int64   -> Integer
54
55         -- plus Eq, Ord, Num, Bounded, Real, Integral, Ix, Enum, Read,
56         --  Show and Bits instances for each of Int8, Int16, Int32 and Int64
57
58 #ifndef __HUGS__
59         -- The "official" place to get these from is Addr, importing
60         -- them from Int is a non-standard thing to do.
61         , indexInt8OffAddr
62         , indexInt16OffAddr
63         , indexInt32OffAddr
64         , indexInt64OffAddr
65         
66         , readInt8OffAddr
67         , readInt16OffAddr
68         , readInt32OffAddr
69         , readInt64OffAddr
70         
71         , writeInt8OffAddr
72         , writeInt16OffAddr
73         , writeInt32OffAddr
74         , writeInt64OffAddr
75
76 #endif
77         
78         , sizeofInt8
79         , sizeofInt16
80         , sizeofInt32
81         , sizeofInt64
82         
83         -- The "official" place to get these from is Foreign
84 #ifndef __PARALLEL_HASKELL__
85 #ifndef __HUGS__
86         , indexInt8OffForeignObj
87         , indexInt16OffForeignObj
88         , indexInt32OffForeignObj
89         , indexInt64OffForeignObj
90
91         , readInt8OffForeignObj
92         , readInt16OffForeignObj
93         , readInt32OffForeignObj
94         , readInt64OffForeignObj
95
96         , writeInt8OffForeignObj
97         , writeInt16OffForeignObj
98         , writeInt32OffForeignObj
99         , writeInt64OffForeignObj
100 #endif
101 #endif
102         
103         -- The non-standard fromInt and toInt methods
104         , Num( fromInt ), Integral( toInt )
105
106         -- non-standard, GHC specific
107         , intToWord
108
109 #ifndef __HUGS__
110         -- Internal, do not use.
111         , int8ToInt#
112         , int16ToInt#
113         , int32ToInt#
114 #endif
115
116         ) where
117
118 #ifndef __HUGS__
119 import PrelBase
120 import CCall
121 import PrelForeign
122 import PrelIOBase
123 import PrelAddr ( Int64(..), Word64(..), Addr(..), Word(..) )
124 import PrelNum ( Num(..), Integral(..) )        -- To get fromInt/toInt
125 #else
126 import Word
127 #endif
128 import Ix
129 import Bits
130 import Ratio   ( (%) )
131 import Numeric ( readDec )
132 import Word    ( Word32 )
133 \end{code}
134
135 #ifndef __HUGS__
136
137 \begin{code}
138 -----------------------------------------------------------------------------
139 -- The "official" coercion functions
140 -----------------------------------------------------------------------------
141
142 int8ToInt  :: Int8  -> Int
143 int16ToInt :: Int16 -> Int
144 int32ToInt :: Int32 -> Int
145
146 int8ToInt#  :: Int8  -> Int#
147 int16ToInt# :: Int16 -> Int#
148 int32ToInt# :: Int32 -> Int#
149
150 intToInt8  :: Int   -> Int8
151 intToInt16 :: Int   -> Int16
152 intToInt32 :: Int   -> Int32
153
154 int8ToInt16  :: Int8  -> Int16
155 int8ToInt32  :: Int8  -> Int32
156
157 int16ToInt8  :: Int16 -> Int8
158 int16ToInt32 :: Int16 -> Int32
159
160 int32ToInt8  :: Int32 -> Int8
161 int32ToInt16 :: Int32 -> Int16
162
163 int8ToInt16  (I8#  x) = I16# x
164 int8ToInt32  (I8#  x) = I32# x
165 int8ToInt64           = int32ToInt64 . int8ToInt32
166
167 int16ToInt8  (I16# x) = I8#  x
168 int16ToInt32 (I16# x) = I32# x
169 int16ToInt64          = int32ToInt64 . int16ToInt32
170
171 int32ToInt8  (I32# x) = I8#  x
172 int32ToInt16 (I32# x) = I16# x
173
174 --GHC specific
175 intToWord :: Int -> Word
176 intToWord (I# i#) = W# (int2Word# i#)
177 \end{code}
178
179 \subsection[Int8]{The @Int8@ interface}
180
181 \begin{code}
182 data Int8 = I8# Int#
183 instance CCallable Int8
184 instance CReturnable Int8
185
186 int8ToInt (I8# x)  = I# (i8ToInt# x)
187 int8ToInt# (I8# x) = i8ToInt# x
188
189 i8ToInt# :: Int# -> Int#
190 i8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
191    where x' = word2Int# (int2Word# x `and#` int2Word# 0xff#)
192
193 --
194 -- This doesn't perform any bounds checking
195 -- on the value it is passed, nor its sign.
196 -- i.e., show (intToInt8 511) => "-1"
197 --
198 intToInt8 (I# x) = I8# (intToInt8# x)
199
200 intToInt8# :: Int# -> Int#
201 intToInt8# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xff#)
202
203 instance Eq  Int8     where 
204   (I8# x#) == (I8# y#) = x# ==# y#
205   (I8# x#) /= (I8# y#) = x# /=# y#
206
207 instance Ord Int8 where 
208   compare (I8# x#) (I8# y#) = compareInt# (i8ToInt# x#) (i8ToInt# y#)
209
210 compareInt# :: Int# -> Int# -> Ordering
211 compareInt# x# y#
212  | x# <#  y# = LT
213  | x# ==# y# = EQ
214  | otherwise = GT
215
216 instance Num Int8 where
217   (I8# x#) + (I8# y#) = I8# (intToInt8# (x# +# y#))
218   (I8# x#) - (I8# y#) = I8# (intToInt8# (x# -# y#))
219   (I8# x#) * (I8# y#) = I8# (intToInt8# (x# *# y#))
220   negate i@(I8# x#) = 
221      if x# ==# 0#
222       then i
223       else I8# (0x100# -# x#)
224
225   abs           = absReal
226   signum        = signumReal
227   fromInteger (S# i#)    = I8# (intToInt8# i#)
228   fromInteger (J# s# d#) = I8# (intToInt8# (integer2Int# s# d#))
229   fromInt       = intToInt8
230
231 instance Bounded Int8 where
232     minBound = 0x80
233     maxBound = 0x7f 
234
235 instance Real Int8 where
236     toRational x = toInteger x % 1
237
238 instance Integral Int8 where
239     div x y
240        | x > 0 && y < 0 = quotInt8 (x-y-1) y
241        | x < 0 && y > 0 = quotInt8 (x-y+1) y
242        | otherwise      = quotInt8 x y
243
244     quot x@(I8# _) y@(I8# y#)
245        | y# /=# 0# = x `quotInt8` y
246        | otherwise = divZeroError "quot{Int8}" x
247     rem x@(I8# _) y@(I8# y#)
248        | y# /=# 0#  = x `remInt8` y
249        | otherwise  = divZeroError "rem{Int8}" x
250     mod x y
251        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
252        | otherwise = r
253         where r = remInt8 x y
254
255     a@(I8# _) `quotRem` b@(I8# _) = (a `quotInt8` b, a `remInt8` b)
256     toInteger i8  = toInteger (int8ToInt i8)
257     toInt     i8  = int8ToInt i8
258
259 remInt8, quotInt8 :: Int8 -> Int8 -> Int8
260 remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `remInt#`  (i8ToInt# y)))
261 quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `quotInt#` (i8ToInt# y)))
262
263 instance Ix Int8 where
264     range (m,n)          = [m..n]
265     index b@(m,_) i
266               | inRange b i = int8ToInt (i - m)
267               | otherwise   = indexError i b "Int8"
268     inRange (m,n) i      = m <= i && i <= n
269
270 instance Enum Int8 where
271     succ i
272       | i == maxBound = succError "Int8"
273       | otherwise     = i+1
274     pred i
275       | i == minBound = predError "Int8"
276       | otherwise     = i-1
277
278     toEnum x
279       | x >= toInt (minBound::Int8) && x <= toInt (maxBound::Int8) 
280       = intToInt8 x
281       | otherwise
282       = toEnumError "Int8" x (minBound::Int8,maxBound::Int8)
283
284     fromEnum           = int8ToInt
285     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int8)]
286     enumFromThen e1 e2 = 
287              map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int8)]
288                 where 
289                    last 
290                      | e2 < e1   = minBound
291                      | otherwise = maxBound
292
293 instance Read Int8 where
294     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
295
296 instance Show Int8 where
297     showsPrec p i8 = showsPrec p (int8ToInt i8)
298
299 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
300 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
301
302 instance Bits Int8 where
303   (I8# x) .&. (I8# y) = I8# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
304   (I8# x) .|. (I8# y) = I8# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
305   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
306   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
307   shift (I8# x) i@(I# i#)
308         | i > 0     = I8# (intToInt8# (iShiftL# (i8ToInt# x)  i#))
309         | otherwise = I8# (intToInt8# (iShiftRA# (i8ToInt# x) (negateInt# i#)))
310   i8@(I8# x)  `rotate` (I# i)
311         | i ==# 0#    = i8
312         | i ># 0#     = 
313              I8# (intToInt8# ( word2Int#  (
314                      (int2Word# (iShiftL# (i8ToInt# x) i'))
315                              `or#`
316                      (int2Word# (iShiftRA# (word2Int# (
317                                                 (int2Word# x) `and#` 
318                                                 (int2Word# (0x100# -# pow2# i2))))
319                                           i2)))))
320         | otherwise = rotate i8 (I# (8# +# i))
321           where
322            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
323            i2 = 8# -# i'
324   bit i         = shift 1 i
325   setBit x i    = x .|. bit i
326   clearBit x i  = x .&. complement (bit i)
327   complementBit x i = x `xor` bit i
328   testBit x i   = (x .&. bit i) /= 0
329   bitSize  _    = 8
330   isSigned _    = True
331
332 pow2# :: Int# -> Int#
333 pow2# x# = iShiftL# 1# x#
334
335 pow2_64# :: Int# -> Int64#
336 pow2_64# x# = word64ToInt64# (shiftL64# (wordToWord64# (int2Word# 1#)) x#)
337
338 sizeofInt8 :: Word32
339 sizeofInt8 = 1
340 \end{code}
341
342 \subsection[Int16]{The @Int16@ interface}
343
344 \begin{code}
345 data Int16  = I16# Int#
346 instance CCallable Int16
347 instance CReturnable Int16
348
349 int16ToInt  (I16# x) = I# (i16ToInt# x)
350 int16ToInt# (I16# x) = i16ToInt# x
351
352 i16ToInt# :: Int# -> Int#
353 i16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
354    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
355
356 intToInt16 (I# x) = I16# (intToInt16# x)
357
358 intToInt16# :: Int# -> Int#
359 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
360
361 instance Eq  Int16     where
362   (I16# x#) == (I16# y#) = x# ==# y#
363   (I16# x#) /= (I16# y#) = x# /=# y#
364
365 instance Ord Int16 where
366   compare (I16# x#) (I16# y#) = compareInt# (i16ToInt# x#) (i16ToInt# y#)
367
368 instance Num Int16 where
369   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
370   (I16# x#) - (I16# y#) = I16# (intToInt16# (x# -# y#))
371   (I16# x#) * (I16# y#) = I16# (intToInt16# (x# *# y#))
372   negate i@(I16# x#) = 
373      if x# ==# 0#
374       then i
375       else I16# (0x10000# -# x#)
376   abs           = absReal
377   signum        = signumReal
378   fromInteger (S# i#)    = I16# (intToInt16# i#)
379   fromInteger (J# s# d#) = I16# (intToInt16# (integer2Int# s# d#))
380   fromInt       = intToInt16
381
382 instance Bounded Int16 where
383     minBound = 0x8000
384     maxBound = 0x7fff 
385
386 instance Real Int16 where
387     toRational x = toInteger x % 1
388
389 instance Integral Int16 where
390     div x y
391        | x > 0 && y < 0 = quotInt16 (x-y-1) y
392        | x < 0 && y > 0 = quotInt16 (x-y+1) y
393        | otherwise      = quotInt16 x y
394
395     quot x@(I16# _) y@(I16# y#)
396        | y# /=# 0#      = x `quotInt16` y
397        | otherwise      = divZeroError "quot{Int16}" x
398     rem x@(I16# _) y@(I16# y#)
399        | y# /=# 0#      = x `remInt16` y
400        | otherwise      = divZeroError "rem{Int16}" x
401     mod x y
402        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
403        | otherwise                        = r
404         where r = remInt16 x y
405
406     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
407     toInteger i16  = toInteger (int16ToInt i16)
408     toInt     i16  = int16ToInt i16
409
410 remInt16, quotInt16 :: Int16 -> Int16 -> Int16
411 remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `remInt#` (i16ToInt# y)))
412 quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `quotInt#` (i16ToInt# y)))
413
414 instance Ix Int16 where
415     range (m,n)          = [m..n]
416     index b@(m,_) i
417               | inRange b i = int16ToInt (i - m)
418               | otherwise   = indexError i b "Int16"
419     inRange (m,n) i      = m <= i && i <= n
420
421 instance Enum Int16 where
422     succ i
423       | i == maxBound = succError "Int16"
424       | otherwise     = i+1
425
426     pred i
427       | i == minBound = predError "Int16"
428       | otherwise     = i-1
429
430     toEnum x
431       | x >= toInt (minBound::Int16) && x <= toInt (maxBound::Int16) 
432       = intToInt16 x
433       | otherwise
434       = toEnumError "Int16" x (minBound::Int16, maxBound::Int16)
435
436     fromEnum         = int16ToInt
437
438     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int16)]
439     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int16)]
440                           where last 
441                                   | e2 < e1   = minBound
442                                   | otherwise = maxBound
443
444 instance Read Int16 where
445     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
446
447 instance Show Int16 where
448     showsPrec p i16 = showsPrec p (int16ToInt i16)
449
450 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
451 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
452
453 instance Bits Int16 where
454   (I16# x) .&. (I16# y) = I16# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
455   (I16# x) .|. (I16# y) = I16# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
456   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
457   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
458   shift (I16# x) i@(I# i#)
459         | i > 0     = I16# (intToInt16# (iShiftL# (i16ToInt# x)  i#))
460         | otherwise = I16# (intToInt16# (iShiftRA# (i16ToInt# x) (negateInt# i#)))
461   i16@(I16# x)  `rotate` (I# i)
462         | i ==# 0#    = i16
463         | i ># 0#     = 
464              I16# (intToInt16# (word2Int# (
465                     (int2Word# (iShiftL# (i16ToInt# x) i')) 
466                              `or#`
467                     (int2Word# (iShiftRA# ( word2Int# (
468                                     (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
469                                           i2)))))
470         | otherwise = rotate i16 (I# (16# +# i))
471           where
472            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
473            i2 = 16# -# i'
474   bit i             = shift 1 i
475   setBit x i        = x .|. bit i
476   clearBit x i      = x .&. complement (bit i)
477   complementBit x i = x `xor` bit i
478   testBit x i       = (x .&. bit i) /= 0
479   bitSize  _        = 16
480   isSigned _        = True
481
482 sizeofInt16 :: Word32
483 sizeofInt16 = 2
484 \end{code}
485
486 %
487 %
488 \subsection[Int32]{The @Int32@ interface}
489 %
490 %
491
492 \begin{code}
493 data Int32  = I32# Int#
494 instance CCallable Int32
495 instance CReturnable Int32
496
497 int32ToInt  (I32# x) = I# (i32ToInt# x)
498 int32ToInt# (I32# x) = i32ToInt# x
499
500 i32ToInt# :: Int# -> Int#
501 #if WORD_SIZE_IN_BYTES > 4
502 i32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
503    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
504 #else
505 i32ToInt# x = x
506 #endif
507
508 intToInt32 (I# x) = I32# (intToInt32# x)
509 intToInt32# :: Int# -> Int#
510 #if WORD_SIZE_IN_BYTES > 4
511 intToInt32# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffffffff#)
512 #else
513 intToInt32# i# = i#
514 #endif
515
516 instance Eq  Int32     where
517   (I32# x#) == (I32# y#) = x# ==# y#
518   (I32# x#) /= (I32# y#) = x# /=# y#
519
520 instance Ord Int32    where
521   compare (I32# x#) (I32# y#) = compareInt# (i32ToInt# x#) (i32ToInt# y#)
522
523 instance Num Int32 where
524   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
525   (I32# x#) - (I32# y#) = I32# (intToInt32# (x# -# y#))
526   (I32# x#) * (I32# y#) = I32# (intToInt32# (x# *# y#))
527 #if WORD_SIZE_IN_BYTES > 4
528   negate i@(I32# x)  = 
529       if x ==# 0#
530        then i
531        else I32# (intToInt32# (0x100000000# -# x'))
532 #else
533   negate (I32# x)  = I32# (negateInt# x)
534 #endif
535   abs           = absReal
536   signum        = signumReal
537   fromInteger (S# i#)    = I32# (intToInt32# i#)
538   fromInteger (J# s# d#) = I32# (intToInt32# (integer2Int# s# d#))
539   fromInt       = intToInt32
540
541 instance Bounded Int32 where 
542     minBound = fromInt minBound
543     maxBound = fromInt maxBound
544
545 instance Real Int32 where
546     toRational x = toInteger x % 1
547
548 instance Integral Int32 where
549     div x y
550        | x > 0 && y < 0 = quotInt32 (x-y-1) y
551        | x < 0 && y > 0 = quotInt32 (x-y+1) y
552        | otherwise      = quotInt32 x y
553     quot x@(I32# _) y@(I32# y#)
554        | y# /=# 0#  = x `quotInt32` y
555        | otherwise  = divZeroError "quot{Int32}" x
556     rem x@(I32# _) y@(I32# y#)
557        | y# /=# 0#  = x `remInt32` y
558        | otherwise  = divZeroError "rem{Int32}" x
559     mod x y
560        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
561        | otherwise                        = r
562         where r = remInt32 x y
563
564     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
565     toInteger i32  = toInteger (int32ToInt i32)
566     toInt     i32  = int32ToInt i32
567
568 remInt32, quotInt32 :: Int32 -> Int32 -> Int32
569 remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `remInt#` (i32ToInt# y)))
570 quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `quotInt#` (i32ToInt# y)))
571
572 instance Ix Int32 where
573     range (m,n)          = [m..n]
574     index b@(m,_) i
575               | inRange b i = int32ToInt (i - m)
576               | otherwise   = indexError i b "Int32"
577     inRange (m,n) i      = m <= i && i <= n
578
579 instance Enum Int32 where
580     succ i
581       | i == maxBound = succError "Int32"
582       | otherwise     = i+1
583
584     pred i
585       | i == minBound = predError "Int32"
586       | otherwise     = i-1
587
588     toEnum x
589         -- with Int having the same range as Int32, the following test
590         -- shouldn't fail. However, having it here 
591       | x >= toInt (minBound::Int32) && x <= toInt (maxBound::Int32) 
592       = intToInt32 x
593       | otherwise
594       = toEnumError "Int32" x (minBound::Int32, maxBound::Int32)
595
596     fromEnum           = int32ToInt
597
598     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int32)]
599     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int32)]
600                           where 
601                             last
602                              | e2 < e1   = minBound
603                              | otherwise = maxBound
604
605 instance Read Int32 where
606     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
607
608 instance Show Int32 where
609     showsPrec p i32 = showsPrec p (int32ToInt i32)
610
611 instance Bits Int32 where
612   (I32# x) .&. (I32# y)   = I32# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
613   (I32# x) .|. (I32# y)   = I32# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
614   (I32# x) `xor` (I32# y) = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
615 #if WORD_SIZE_IN_BYTES > 4
616   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffffffff#)))
617 #else
618   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
619 #endif
620   shift (I32# x) i@(I# i#)
621         | i > 0     = I32# (intToInt32# (iShiftL# (i32ToInt# x)  i#))
622         | otherwise = I32# (intToInt32# (iShiftRA# (i32ToInt# x) (negateInt# i#)))
623   i32@(I32# x)  `rotate` (I# i)
624         | i ==# 0#    = i32
625         | i ># 0#     = 
626              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
627              I32# (intToInt32# ( word2Int# (
628                     (int2Word# (iShiftL# (i32ToInt# x) i')) 
629                           `or#`
630                     (int2Word# (iShiftRA# (word2Int# (
631                                               (int2Word# x) 
632                                                   `and#` 
633                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
634                                           i2)))))
635         | otherwise = rotate i32 (I# (32# +# i))
636           where
637            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
638            i2 = 32# -# i'
639            (I32# maxBound#) = maxBound
640   bit i         = shift 1 i
641   setBit x i    = x .|. bit i
642   clearBit x i  = x .&. complement (bit i)
643   complementBit x i = x `xor` bit i
644   testBit x i   = (x .&. bit i) /= 0
645   bitSize  _    = 32
646   isSigned _    = True
647
648 sizeofInt32 :: Word32
649 sizeofInt32 = 4
650 \end{code}
651
652 \subsection[Int64]{The @Int64@ interface}
653
654
655 \begin{code}
656 #if WORD_SIZE_IN_BYTES == 8
657 --data Int64 = I64# Int#
658
659 int32ToInt64 :: Int32 -> Int64
660 int32ToInt64 (I32# i#) = I64# i#
661
662 intToInt32# :: Int# -> Int#
663 intToInt32# i# = word2Int# ((int2Word# i#) `and#` (case (maxBound::Word32) of W# x# -> x#))
664
665 int64ToInt32 :: Int64 -> Int32
666 int64ToInt32 (I64# i#) = I32# (intToInt32# w#)
667
668 instance Eq  Int64     where 
669   (I64# x) == (I64# y) = x `eqInt#` y
670   (I64# x) /= (I64# y) = x `neInt#` y
671
672 instance Ord Int32    where
673   compare (I64# x#) (I64# y#) = compareInt# x# y#
674
675 instance Num Int64 where
676   (I64# x) + (I64# y) = I64# (x +# y)
677   (I64# x) - (I64# y) = I64# (x -# y)
678   (I64# x) * (I64# y) = I64# (x *# y)
679   negate w@(I64# x)   = I64# (negateInt# x)
680   abs x               = absReal
681   signum              = signumReal
682   fromInteger (S# i#)    = I64# i#
683   fromInteger (J# s# d#) = I64# (integer2Int# s# d#)
684   fromInt       = intToInt64
685
686 instance Bounded Int64 where
687   minBound = integerToInt64 (-0x8000000000000000)
688   maxBound = integerToInt64 0x7fffffffffffffff
689
690 instance Integral Int64 where
691     div x y
692       | x > 0 && y < 0  = quotInt64 (x-y-1) y
693       | x < 0 && y > 0  = quotInt64 (x-y+1) y
694       | otherwise       = quotInt64 x y
695
696     quot x@(I64# _) y@(I64# y#)
697        | y# /=# 0# = x `quotInt64` y
698        | otherwise = divZeroError "quot{Int64}" x
699
700     rem x@(I64# _) y@(I64# y#)
701        | y# /=# 0# = x `remInt64` y
702        | otherwise = divZeroError "rem{Int64}" x
703
704     mod x y
705        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
706        | otherwise = r
707         where r = remInt64 x y
708
709     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
710     toInteger (I64# i#) = toInteger (I# i#)
711     toInt     (I64# i#) = I# i#
712
713 instance Bits Int64 where
714   (I64# x) .&. (I64# y)   = I64# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
715   (I64# x) .|. (I64# y)   = I64# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
716   (I64# x) `xor` (I64# y) = I64# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
717   complement (I64# x)     = I64# (negateInt# x)
718   shift (I64# x) i@(I# i#)
719         | i > 0     = I64# (iShiftL# x  i#)
720         | otherwise = I64# (iShiftRA# x (negateInt# i#))
721   i64@(I64# x)  `rotate` (I# i)
722         | i ==# 0#    = i64
723         | i ># 0#     = 
724              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
725              I64# (word2Int# (
726                     (int2Word# (iShiftL# x i')) 
727                           `or#`
728                     (int2Word# (iShiftRA# (word2Int# (
729                                               (int2Word# x) 
730                                                   `and#` 
731                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
732                                           i2))))
733         | otherwise = rotate i64 (I# (64# +# i))
734           where
735            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
736            i2 = 64# -# i'
737            (I64# maxBound#) = maxBound
738   bit i         = shift 1 i
739   setBit x i    = x .|. bit i
740   clearBit x i  = x .&. complement (bit i)
741   complementBit x i = x `xor` bit i
742   testBit x i   = (x .&. bit i) /= 0
743   bitSize  _    = 64
744   isSigned _    = True
745
746
747
748 remInt64  (I64# x) (I64# y) = I64# (x `remInt#` y)
749 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt#` y)
750
751 int64ToInteger :: Int64 -> Integer
752 int64ToInteger (I64# i#) = toInteger (I# i#)
753
754 integerToInt64 :: Integer -> Int64
755 integerToInt64 i = case fromInteger i of { I# i# -> I64# i# }
756
757 intToInt64 :: Int -> Int64
758 intToInt64 (I# i#) = I64# i#
759
760 int64ToInt :: Int64 -> Int
761 int64ToInt (I64# i#) = I# i#
762
763 #else
764 --assume: support for long-longs
765 --data Int64 = I64 Int64# deriving (Eq, Ord, Bounded)
766
767 int32ToInt64 :: Int32 -> Int64
768 int32ToInt64 (I32# i#) = I64# (intToInt64# i#)
769
770 int64ToInt32 :: Int64 -> Int32
771 int64ToInt32 (I64# i#) = I32# (int64ToInt# i#)
772
773 int64ToInteger :: Int64 -> Integer
774 int64ToInteger (I64# x#) = 
775    case int64ToInteger# x# of
776      (# s#, p# #) -> J# s# p#
777
778 integerToInt64 :: Integer -> Int64
779 integerToInt64 (S# i#) = I64# (intToInt64# i#)
780 integerToInt64 (J# s# d#) = I64# (integerToInt64# s# d#)
781
782 instance Eq  Int64     where 
783   (I64# x) == (I64# y) = x `eqInt64#` y
784   (I64# x) /= (I64# y) = x `neInt64#` y
785
786 instance Ord Int64     where 
787   compare (I64# x) (I64# y)   = compareInt64# x y
788   (<)  (I64# x) (I64# y)      = x `ltInt64#` y
789   (<=) (I64# x) (I64# y)      = x `leInt64#` y
790   (>=) (I64# x) (I64# y)      = x `geInt64#` y
791   (>)  (I64# x) (I64# y)      = x `gtInt64#` y
792   max x@(I64# x#) y@(I64# y#) = 
793      case (compareInt64# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
794   min x@(I64# x#) y@(I64# y#) =
795      case (compareInt64# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
796
797 instance Num Int64 where
798   (I64# x) + (I64# y) = I64# (x `plusInt64#`  y)
799   (I64# x) - (I64# y) = I64# (x `minusInt64#` y)
800   (I64# x) * (I64# y) = I64# (x `timesInt64#` y)
801   negate (I64# x)     = I64# (negateInt64# x)
802   abs x               = absReal x
803   signum              = signumReal
804   fromInteger i       = integerToInt64 i
805   fromInt     i       = intToInt64 i
806
807 compareInt64# :: Int64# -> Int64# -> Ordering
808 compareInt64# i# j# 
809  | i# `ltInt64#` j# = LT
810  | i# `eqInt64#` j# = EQ
811  | otherwise        = GT
812
813 instance Bounded Int64 where
814   minBound = integerToInt64 (-0x8000000000000000)
815   maxBound = integerToInt64 0x7fffffffffffffff
816
817 instance Integral Int64 where
818     div x y
819       | x > 0 && y < 0  = quotInt64 (x-y-1) y
820       | x < 0 && y > 0  = quotInt64 (x-y+1) y
821       | otherwise       = quotInt64 x y
822
823     quot x@(I64# _) y@(I64# y#)
824        | y# `neInt64#` (intToInt64# 0#) = x `quotInt64` y
825        | otherwise = divZeroError "quot{Int64}" x
826
827     rem x@(I64# _) y@(I64# y#)
828        | y# `neInt64#` (intToInt64# 0#) = x `remInt64` y
829        | otherwise = divZeroError "rem{Int64}" x
830
831     mod x y
832        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
833        | otherwise = r
834         where r = remInt64 x y
835
836     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
837     toInteger i         = int64ToInteger i
838     toInt     i         = int64ToInt i
839
840 instance Bits Int64 where
841   (I64# x) .&. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `and64#` (int64ToWord64# y)))
842   (I64# x) .|. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `or64#`  (int64ToWord64# y)))
843   (I64# x) `xor` (I64# y) = I64# (word64ToInt64# ((int64ToWord64# x) `xor64#` (int64ToWord64# y)))
844   complement (I64# x)     = I64# (negateInt64# x)
845   shift (I64# x) i@(I# i#)
846         | i > 0     = I64# (iShiftL64# x  i#)
847         | otherwise = I64# (iShiftRA64# x (negateInt# i#))
848   i64@(I64# x)  `rotate` (I# i)
849         | i ==# 0#    = i64
850         | i ># 0#     = 
851              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
852              I64# (word64ToInt64# (
853                     (int64ToWord64# (iShiftL64# x i'))                    `or64#`
854                     (int64ToWord64# (iShiftRA64# (word64ToInt64# ((int64ToWord64# x)     `and64#` 
855                                                  (int64ToWord64# (maxBound# `minusInt64#` (pow2_64# i2 `plusInt64#` (intToInt64# 1#))))))
856                                                 i2))))
857         | otherwise = rotate i64 (I# (64# +# i))
858           where
859            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
860            i2 = 64# -# i'
861            (I64# maxBound#) = maxBound
862   bit i         = shift 1 i
863   setBit x i    = x .|. bit i
864   clearBit x i  = x .&. complement (bit i)
865   complementBit x i = x `xor` bit i
866   testBit x i   = (x .&. bit i) /= 0
867   bitSize  _    = 64
868   isSigned _    = True
869
870 remInt64, quotInt64 :: Int64 -> Int64 -> Int64
871 remInt64  (I64# x) (I64# y) = I64# (x `remInt64#` y)
872 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt64#` y)
873
874 intToInt64 :: Int -> Int64
875 intToInt64 (I# i#) = I64# (intToInt64# i#)
876
877 int64ToInt :: Int64 -> Int
878 int64ToInt (I64# i#) = I# (int64ToInt# i#)
879
880 -- Word64# primop wrappers:
881
882 ltInt64# :: Int64# -> Int64# -> Bool
883 ltInt64# x# y# =  
884         case stg_ltInt64 x# y# of
885           0 -> False
886           _ -> True
887       
888 leInt64# :: Int64# -> Int64# -> Bool
889 leInt64# x# y# =  
890         case stg_leInt64 x# y# of
891           0 -> False
892           _ -> True
893
894 eqInt64# :: Int64# -> Int64# -> Bool
895 eqInt64# x# y# =  
896         case stg_eqInt64 x# y# of
897           0 -> False
898           _ -> True
899
900 neInt64# :: Int64# -> Int64# -> Bool
901 neInt64# x# y# =  
902         case stg_neInt64 x# y# of
903           0 -> False
904           _ -> True
905
906 geInt64# :: Int64# -> Int64# -> Bool
907 geInt64# x# y# =  
908         case stg_geInt64 x# y# of
909           0 -> False
910           _ -> True
911
912 gtInt64# :: Int64# -> Int64# -> Bool
913 gtInt64# x# y# =  
914         case stg_gtInt64 x# y# of
915           0 -> False
916           _ -> True
917
918 plusInt64# :: Int64# -> Int64# -> Int64#
919 plusInt64# a# b# = 
920   case stg_plusInt64 a# b# of
921     I64# i# -> i#
922
923 minusInt64# :: Int64# -> Int64# -> Int64#
924 minusInt64# a# b# =
925   case stg_minusInt64 a# b# of
926     I64# i# -> i#
927
928 timesInt64# :: Int64# -> Int64# -> Int64#
929 timesInt64# a# b# =
930   case stg_timesInt64 a# b# of
931     I64# i# -> i#
932
933 quotInt64# :: Int64# -> Int64# -> Int64#
934 quotInt64# a# b# =
935   case stg_quotInt64 a# b# of
936     I64# i# -> i#
937
938 remInt64# :: Int64# -> Int64# -> Int64#
939 remInt64# a# b# =
940   case stg_remInt64 a# b# of
941     I64# i# -> i#
942
943 negateInt64# :: Int64# -> Int64#
944 negateInt64# a# =
945   case stg_negateInt64 a# of
946     I64# i# -> i#
947
948 and64# :: Word64# -> Word64# -> Word64#
949 and64# a# b# =
950   case stg_and64 a# b# of
951     W64# w# -> w#
952
953 or64# :: Word64# -> Word64# -> Word64#
954 or64# a# b# =
955   case stg_or64 a# b# of
956     W64# w# -> w#
957
958 xor64# :: Word64# -> Word64# -> Word64#
959 xor64# a# b# = 
960   case stg_xor64 a# b# of
961     W64# w# -> w#
962
963 not64# :: Word64# -> Word64#
964 not64# a# = 
965   case stg_not64 a# of
966     W64# w# -> w#
967
968 shiftL64# :: Word64# -> Int# -> Word64#
969 shiftL64# a# b# =
970   case stg_shiftL64 a# b# of
971     W64# w# -> w#
972
973 iShiftL64# :: Int64# -> Int# -> Int64#
974 iShiftL64# a# b# =
975   case stg_iShiftL64 a# b# of
976     I64# i# -> i#
977
978 iShiftRL64# :: Int64# -> Int# -> Int64#
979 iShiftRL64# a# b# =
980   case stg_iShiftRL64 a# b# of
981     I64# i# -> i#
982
983 iShiftRA64# :: Int64# -> Int# -> Int64#
984 iShiftRA64# a# b# =
985   case stg_iShiftRA64 a# b# of
986     I64# i# -> i#
987
988 shiftRL64# :: Word64# -> Int# -> Word64#
989 shiftRL64# a# b# =
990   case stg_shiftRL64 a# b# of
991     W64# w# -> w#
992
993 int64ToInt# :: Int64# -> Int#
994 int64ToInt# i64# =
995   case stg_int64ToInt i64# of
996     I# i# -> i#
997
998 wordToWord64# :: Word# -> Word64#
999 wordToWord64# w# =
1000   case stg_wordToWord64 w# of
1001     W64# w64# -> w64#
1002
1003 word64ToInt64# :: Word64# -> Int64#
1004 word64ToInt64# w# =
1005   case stg_word64ToInt64 w# of
1006     I64# i# -> i#
1007
1008 int64ToWord64# :: Int64# -> Word64#
1009 int64ToWord64# i# =
1010   case stg_int64ToWord64 i# of
1011     W64# w# -> w#
1012
1013 intToInt64# :: Int# -> Int64#
1014 intToInt64# i# =
1015   case stg_intToInt64 i# of
1016     I64# i64# -> i64#
1017
1018 foreign import "stg_intToInt64" stg_intToInt64 :: Int# -> Int64
1019 foreign import "stg_int64ToWord64" stg_int64ToWord64 :: Int64# -> Word64
1020 foreign import "stg_word64ToInt64" stg_word64ToInt64 :: Word64# -> Int64
1021 foreign import "stg_wordToWord64" stg_wordToWord64 :: Word# -> Word64
1022 foreign import "stg_int64ToInt" stg_int64ToInt :: Int64# -> Int
1023 foreign import "stg_shiftRL64" stg_shiftRL64 :: Word64# -> Int# -> Word64
1024 foreign import "stg_iShiftRA64" stg_iShiftRA64 :: Int64# -> Int# -> Int64
1025 foreign import "stg_iShiftRL64" stg_iShiftRL64 :: Int64# -> Int# -> Int64
1026 foreign import "stg_iShiftL64" stg_iShiftL64 :: Int64# -> Int# -> Int64
1027 foreign import "stg_shiftL64" stg_shiftL64 :: Word64# -> Int# -> Word64
1028 foreign import "stg_not64" stg_not64 :: Word64# -> Word64
1029 foreign import "stg_xor64" stg_xor64 :: Word64# -> Word64# -> Word64
1030 foreign import "stg_or64" stg_or64 :: Word64# -> Word64# -> Word64
1031 foreign import "stg_and64" stg_and64 :: Word64# -> Word64# -> Word64
1032 foreign import "stg_negateInt64" stg_negateInt64 :: Int64# -> Int64
1033 foreign import "stg_remInt64" stg_remInt64 :: Int64# -> Int64# -> Int64
1034 foreign import "stg_quotInt64" stg_quotInt64 :: Int64# -> Int64# -> Int64
1035 foreign import "stg_timesInt64" stg_timesInt64 :: Int64# -> Int64# -> Int64
1036 foreign import "stg_minusInt64" stg_minusInt64 :: Int64# -> Int64# -> Int64
1037 foreign import "stg_plusInt64" stg_plusInt64 :: Int64# -> Int64# -> Int64
1038 foreign import "stg_gtInt64" stg_gtInt64 :: Int64# -> Int64# -> Int
1039 foreign import "stg_geInt64" stg_geInt64 :: Int64# -> Int64# -> Int
1040 foreign import "stg_neInt64" stg_neInt64 :: Int64# -> Int64# -> Int
1041 foreign import "stg_eqInt64" stg_eqInt64 :: Int64# -> Int64# -> Int
1042 foreign import "stg_leInt64" stg_leInt64 :: Int64# -> Int64# -> Int
1043 foreign import "stg_ltInt64" stg_ltInt64 :: Int64# -> Int64# -> Int
1044
1045 #endif
1046
1047 --
1048 -- Code that's independent of Int64 rep.
1049 -- 
1050 instance Enum Int64 where
1051     succ i
1052       | i == maxBound = succError "Int64"
1053       | otherwise     = i+1
1054
1055     pred i
1056       | i == minBound = predError "Int64"
1057       | otherwise     = i-1
1058
1059     toEnum    i = intToInt64 i
1060     fromEnum  x
1061       | x >= intToInt64 (minBound::Int) && x <= intToInt64 (maxBound::Int)
1062       = int64ToInt x
1063       | otherwise
1064       = fromEnumError "Int64" x
1065
1066     enumFrom e1        = map integerToInt64 [int64ToInteger e1 .. int64ToInteger (maxBound::Int64)]
1067     enumFromTo e1 e2   = map integerToInt64 [int64ToInteger e1 .. int64ToInteger e2]
1068     enumFromThen e1 e2 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger last]
1069                        where 
1070                           last :: Int64
1071                           last 
1072                            | e2 < e1   = minBound
1073                            | otherwise = maxBound
1074
1075     enumFromThenTo e1 e2 e3 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger e3]
1076
1077
1078 instance Show Int64 where
1079     showsPrec p i64 = showsPrec p (int64ToInteger i64)
1080
1081 instance Read Int64 where
1082   readsPrec _ s = [ (integerToInt64 x,r) | (x,r) <- readDec s ]
1083
1084
1085 instance Ix Int64 where
1086     range (m,n)          = [m..n]
1087     index b@(m,_) i
1088            | inRange b i = int64ToInt (i-m)
1089            | otherwise   = indexError i b "Int64"
1090     inRange (m,n) i      = m <= i && i <= n
1091
1092 instance Real Int64 where
1093   toRational x = toInteger x % 1
1094
1095
1096 sizeofInt64 :: Word32
1097 sizeofInt64 = 8
1098
1099 int8ToInteger :: Int8 -> Integer
1100 int8ToInteger i = toInteger i
1101
1102 int16ToInteger :: Int16 -> Integer
1103 int16ToInteger i = toInteger i
1104
1105 int32ToInteger :: Int32 -> Integer
1106 int32ToInteger i = toInteger i
1107
1108 int64ToInt8 :: Int64 -> Int8
1109 int64ToInt8 = int32ToInt8 . int64ToInt32
1110
1111 int64ToInt16 :: Int64 -> Int16
1112 int64ToInt16 = int32ToInt16 . int64ToInt32
1113
1114 integerToInt8 :: Integer -> Int8
1115 integerToInt8 = fromInteger
1116
1117 integerToInt16 :: Integer -> Int16
1118 integerToInt16 = fromInteger
1119
1120 integerToInt32 :: Integer -> Int32
1121 integerToInt32 = fromInteger
1122
1123 \end{code}
1124
1125 %
1126 %
1127 \subsection[Int Utils]{Miscellaneous utilities}
1128 %
1129 %
1130
1131 Code copied from the Prelude
1132
1133 \begin{code}
1134 absReal :: (Ord a, Num a) => a -> a
1135 absReal x    | x >= 0    = x
1136              | otherwise = -x
1137
1138 signumReal :: (Ord a, Num a) => a -> a
1139 signumReal x | x == 0    =  0
1140              | x > 0     =  1
1141              | otherwise = -1
1142 \end{code}
1143
1144 \begin{code}
1145 indexInt8OffAddr  :: Addr -> Int -> Int8
1146 indexInt8OffAddr (A# a#) (I# i#) = intToInt8 (I# (ord# (indexCharOffAddr# a# i#)))
1147
1148 indexInt16OffAddr :: Addr -> Int -> Int16
1149 indexInt16OffAddr a i =
1150 #ifdef WORDS_BIGENDIAN
1151   intToInt16 ( int8ToInt l + (int8ToInt maxBound) * int8ToInt h)
1152 #else
1153   intToInt16 ( int8ToInt h + (int8ToInt maxBound) * int8ToInt l)
1154 #endif
1155  where
1156    byte_idx = i * 2
1157    l = indexInt8OffAddr a byte_idx
1158    h = indexInt8OffAddr a (byte_idx+1)
1159
1160 indexInt32OffAddr :: Addr -> Int -> Int32
1161 indexInt32OffAddr (A# a#) i = intToInt32 (I# (indexIntOffAddr# a# i'#))
1162  where
1163    -- adjust index to be in Int units, not Int32 ones.
1164   (I# i'#) 
1165 #if WORD_SIZE_IN_BYTES==8
1166    = i `div` 2
1167 #else
1168    = i
1169 #endif
1170
1171 indexInt64OffAddr :: Addr -> Int -> Int64
1172 indexInt64OffAddr (A# a#) (I# i#)
1173 #if WORD_SIZE_IN_BYTES==8
1174  = I64# (indexIntOffAddr# a# i#)
1175 #else
1176  = I64# (indexInt64OffAddr# a# i#)
1177 #endif
1178
1179 #ifndef __PARALLEL_HASKELL__
1180
1181 indexInt8OffForeignObj  :: ForeignObj -> Int -> Int8
1182 indexInt8OffForeignObj (ForeignObj fo#) (I# i#) = intToInt8 (I# (ord# (indexCharOffForeignObj# fo# i#)))
1183
1184 indexInt16OffForeignObj :: ForeignObj -> Int -> Int16
1185 indexInt16OffForeignObj fo i =
1186 # ifdef WORDS_BIGENDIAN
1187   intToInt16 ( int8ToInt l + (int8ToInt maxBound) * int8ToInt h)
1188 # else
1189   intToInt16 ( int8ToInt h + (int8ToInt maxBound) * int8ToInt l)
1190 # endif
1191  where
1192    byte_idx = i * 2
1193    l = indexInt8OffForeignObj fo byte_idx
1194    h = indexInt8OffForeignObj fo (byte_idx+1)
1195
1196 indexInt32OffForeignObj :: ForeignObj -> Int -> Int32
1197 indexInt32OffForeignObj (ForeignObj fo#) i = intToInt32 (I# (indexIntOffForeignObj# fo# i'#))
1198  where
1199    -- adjust index to be in Int units, not Int32 ones.
1200   (I# i'#) 
1201 # if WORD_SIZE_IN_BYTES==8
1202    = i `div` 2
1203 # else
1204    = i
1205 # endif
1206
1207 indexInt64OffForeignObj :: ForeignObj -> Int -> Int64
1208 indexInt64OffForeignObj (ForeignObj fo#) (I# i#)
1209 # if WORD_SIZE_IN_BYTES==8
1210  = I64# (indexIntOffForeignObj# fo# i#)
1211 # else
1212  = I64# (indexInt64OffForeignObj# fo# i#)
1213 # endif
1214
1215 #endif /* __PARALLEL_HASKELL__ */
1216 \end{code}
1217
1218 Read words out of mutable memory:
1219
1220 \begin{code}
1221 readInt8OffAddr :: Addr -> Int -> IO Int8
1222 readInt8OffAddr a i = _casm_ `` %r=(StgInt8)(((StgInt8*)%0)[(StgInt)%1]); '' a i
1223
1224 readInt16OffAddr  :: Addr -> Int -> IO Int16
1225 readInt16OffAddr a i = _casm_ `` %r=(StgInt16)(((StgInt16*)%0)[(StgInt)%1]); '' a i
1226
1227 readInt32OffAddr  :: Addr -> Int -> IO Int32
1228 readInt32OffAddr a i = _casm_ `` %r=(StgInt32)(((StgInt32*)%0)[(StgInt)%1]); '' a i
1229
1230 readInt64OffAddr  :: Addr -> Int -> IO Int64
1231 #if WORD_SIZE_IN_BYTES==8
1232 readInt64OffAddr a i = _casm_ `` %r=(StgInt)(((StgInt*)%0)[(StgInt)%1]); '' a i
1233 #else
1234 readInt64OffAddr a i = _casm_ `` %r=(StgInt64)(((StgInt64*)%0)[(StgInt)%1]); '' a i
1235 #endif
1236
1237 #ifndef __PARALLEL_HASKELL__
1238
1239 readInt8OffForeignObj :: ForeignObj -> Int -> IO Int8
1240 readInt8OffForeignObj fo i = _casm_ `` %r=(StgInt8)(((StgInt8*)%0)[(StgInt)%1]); '' fo i
1241
1242 readInt16OffForeignObj  :: ForeignObj -> Int -> IO Int16
1243 readInt16OffForeignObj fo i = _casm_ `` %r=(StgInt16)(((StgInt16*)%0)[(StgInt)%1]); '' fo i
1244
1245 readInt32OffForeignObj  :: ForeignObj -> Int -> IO Int32
1246 readInt32OffForeignObj fo i = _casm_ `` %r=(StgInt32)(((StgInt32*)%0)[(StgInt)%1]); '' fo i
1247
1248 readInt64OffForeignObj  :: ForeignObj -> Int -> IO Int64
1249 # if WORD_SIZE_IN_BYTES==8
1250 readInt64OffForeignObj fo i = _casm_ `` %r=(StgInt)(((StgInt*)%0)[(StgInt)%1]); '' fo i
1251 # else
1252 readInt64OffForeignObj fo i = _casm_ `` %r=(StgInt64)(((StgInt64*)%0)[(StgInt)%1]); '' fo i
1253 # endif
1254
1255 #endif /* __PARALLEL_HASKELL__ */
1256 \end{code}
1257
1258 \begin{code}
1259 writeInt8OffAddr  :: Addr -> Int -> Int8  -> IO ()
1260 writeInt8OffAddr a i e = _casm_ `` (((StgInt8*)%0)[(StgInt)%1])=(StgInt8)%2; '' a i e
1261
1262 writeInt16OffAddr :: Addr -> Int -> Int16 -> IO ()
1263 writeInt16OffAddr a i e = _casm_ `` (((StgInt16*)%0)[(StgInt)%1])=(StgInt16)%2; '' a i e
1264
1265 writeInt32OffAddr :: Addr -> Int -> Int32 -> IO ()
1266 writeInt32OffAddr a i e = _casm_ `` (((StgInt32*)%0)[(StgInt)%1])=(StgInt32)%2; '' a i e
1267
1268 writeInt64OffAddr :: Addr -> Int -> Int64 -> IO ()
1269 #if WORD_SIZE_IN_BYTES==8
1270 writeInt64OffAddr a i e = _casm_ `` (((StgInt*)%0)[(StgInt)%1])=(StgInt)%2; '' a i e
1271 #else
1272 writeInt64OffAddr a i e = _casm_ `` (((StgInt64*)%0)[(StgInt)%1])=(StgInt64)%2; '' a i e
1273 #endif
1274
1275 #ifndef __PARALLEL_HASKELL__
1276
1277 writeInt8OffForeignObj  :: ForeignObj -> Int -> Int8  -> IO ()
1278 writeInt8OffForeignObj fo i e = _casm_ `` (((StgInt8*)%0)[(StgInt)%1])=(StgInt8)%2; '' fo i e
1279
1280 writeInt16OffForeignObj :: ForeignObj -> Int -> Int16 -> IO ()
1281 writeInt16OffForeignObj fo i e = _casm_ `` (((StgInt16*)%0)[(StgInt)%1])=(StgInt16)%2; '' fo i e
1282
1283 writeInt32OffForeignObj :: ForeignObj -> Int -> Int32 -> IO ()
1284 writeInt32OffForeignObj fo i e = _casm_ `` (((StgInt32*)%0)[(StgInt)%1])=(StgInt32)%2; '' fo i e
1285
1286 writeInt64OffForeignObj :: ForeignObj -> Int -> Int64 -> IO ()
1287 # if WORD_SIZE_IN_BYTES==8
1288 writeInt64OffForeignObj fo i e = _casm_ `` (((StgInt*)%0)[(StgInt)%1])=(StgInt)%2; '' fo i e
1289 # else
1290 writeInt64OffForeignObj fo i e = _casm_ `` (((StgInt64*)%0)[(StgInt)%1])=(StgInt64)%2; '' fo i e
1291 # endif
1292
1293 #endif /* __PARALLEL_HASKELL__ */
1294
1295 \end{code}
1296
1297
1298 C&P'ed from Ix.lhs
1299
1300 \begin{code}
1301 {-# NOINLINE indexError #-}
1302 indexError :: Show a => a -> (a,a) -> String -> b
1303 indexError i rng tp
1304   = error (showString "Ix{" . showString tp . showString "}.index: Index " .
1305            showParen True (showsPrec 0 i) .
1306            showString " out of range " $
1307            showParen True (showsPrec 0 rng) "")
1308
1309
1310 toEnumError :: (Show a,Show b) => String -> a -> (b,b) -> c
1311 toEnumError inst_ty tag bnds
1312   = error ("Enum.toEnum{" ++ inst_ty ++ "}: tag " ++
1313            (showParen True (showsPrec 0 tag) $
1314              " is outside of bounds " ++
1315              show bnds))
1316
1317 fromEnumError :: (Show a,Show b) => String -> a -> b
1318 fromEnumError inst_ty tag
1319   = error ("Enum.fromEnum{" ++ inst_ty ++ "}: value " ++
1320            (showParen True (showsPrec 0 tag) $
1321              " is outside of Int's bounds " ++
1322              show (minBound::Int,maxBound::Int)))
1323
1324 succError :: String -> a
1325 succError inst_ty
1326   = error ("Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound")
1327
1328 predError :: String -> a
1329 predError inst_ty
1330   = error ("Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound")
1331
1332 divZeroError :: (Show a) => String -> a -> b
1333 divZeroError meth v 
1334   = error ("Integral." ++ meth ++ ": divide by 0 (" ++ show v ++ " / 0)")
1335
1336 \end{code}
1337
1338 #else 
1339 \begin{code}
1340 -----------------------------------------------------------------------------
1341 -- The "official" coercion functions
1342 -----------------------------------------------------------------------------
1343
1344 int8ToInt  :: Int8  -> Int
1345 intToInt8  :: Int   -> Int8
1346 int16ToInt :: Int16 -> Int
1347 intToInt16 :: Int   -> Int16
1348 int32ToInt :: Int32 -> Int
1349 intToInt32 :: Int   -> Int32
1350
1351 -- And some non-exported ones
1352
1353 int8ToInt16  :: Int8  -> Int16
1354 int8ToInt32  :: Int8  -> Int32
1355 int16ToInt8  :: Int16 -> Int8
1356 int16ToInt32 :: Int16 -> Int32
1357 int32ToInt8  :: Int32 -> Int8
1358 int32ToInt16 :: Int32 -> Int16
1359
1360 int8ToInt16  = I16 . int8ToInt
1361 int8ToInt32  = I32 . int8ToInt
1362 int16ToInt8  = I8  . int16ToInt
1363 int16ToInt32 = I32 . int16ToInt
1364 int32ToInt8  = I8  . int32ToInt
1365 int32ToInt16 = I16 . int32ToInt
1366
1367 -----------------------------------------------------------------------------
1368 -- Int8
1369 -----------------------------------------------------------------------------
1370
1371 newtype Int8  = I8 Int
1372
1373 int8ToInt (I8 x) = if x' <= 0x7f then x' else x' - 0x100
1374  where x' = x `primAndInt` 0xff
1375 intToInt8 = I8
1376
1377 instance Eq  Int8     where (==)    = binop (==)
1378 instance Ord Int8     where compare = binop compare
1379
1380 instance Num Int8 where
1381     x + y         = to (binop (+) x y)
1382     x - y         = to (binop (-) x y)
1383     negate        = to . negate . from
1384     x * y         = to (binop (*) x y)
1385     abs           = absReal
1386     signum        = signumReal
1387     fromInteger   = to . fromInteger
1388     fromInt       = to
1389
1390 instance Bounded Int8 where
1391     minBound = 0x80
1392     maxBound = 0x7f 
1393
1394 instance Real Int8 where
1395     toRational x = toInteger x % 1
1396
1397 instance Integral Int8 where
1398     x `div` y     = to  (binop div x y)
1399     x `quot` y    = to  (binop quot x y)
1400     x `rem` y     = to  (binop rem x y)
1401     x `mod` y     = to  (binop mod x y)
1402     x `quotRem` y = to2 (binop quotRem x y)
1403     even          = even      . from
1404     toInteger     = toInteger . from
1405     toInt         = toInt     . from
1406
1407 instance Ix Int8 where
1408     range (m,n)          = [m..n]
1409     index b@(m,n) i
1410               | inRange b i = from (i - m)
1411               | otherwise   = error "index: Index out of range"
1412     inRange (m,n) i      = m <= i && i <= n
1413
1414 instance Enum Int8 where
1415     toEnum         = to 
1416     fromEnum       = from
1417     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int8)]
1418     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int8)]
1419                           where last = if d < c then minBound else maxBound
1420
1421 instance Read Int8 where
1422     readsPrec p s = [ (to x,r) | (x,r) <- readsPrec p s ]
1423
1424 instance Show Int8 where
1425     showsPrec p = showsPrec p . from
1426
1427 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
1428 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
1429
1430 instance Bits Int8 where
1431   x .&. y       = int32ToInt8 (binop8 (.&.) x y)
1432   x .|. y       = int32ToInt8 (binop8 (.|.) x y)
1433   x `xor` y     = int32ToInt8 (binop8 xor x y)
1434   complement    = int32ToInt8 . complement . int8ToInt32
1435   x `shift` i   = int32ToInt8 (int8ToInt32 x `shift` i)
1436 --  rotate      
1437   bit           = int32ToInt8 . bit
1438   setBit x i    = int32ToInt8 (setBit (int8ToInt32 x) i)
1439   clearBit x i  = int32ToInt8 (clearBit (int8ToInt32 x) i)
1440   complementBit x i = int32ToInt8 (complementBit (int8ToInt32 x) i)
1441   testBit x i   = testBit (int8ToInt32 x) i
1442   bitSize  _    = 8
1443   isSigned _    = True
1444
1445 int8ToInteger = error "TODO: int8ToInteger"
1446 integerToInt8 = error "TODO: integerToInt8"
1447
1448 --intToInt8 = fromInt
1449 --int8ToInt = toInt
1450
1451 sizeofInt8 :: Word32
1452 sizeofInt8 =  1
1453
1454 -----------------------------------------------------------------------------
1455 -- Int16
1456 -----------------------------------------------------------------------------
1457
1458 newtype Int16  = I16 Int
1459
1460 int16ToInt (I16 x) = if x' <= 0x7fff then x' else x' - 0x10000
1461  where x' = x `primAndInt` 0xffff
1462 intToInt16 = I16
1463
1464 instance Eq  Int16     where (==)    = binop (==)
1465 instance Ord Int16     where compare = binop compare
1466
1467 instance Num Int16 where
1468     x + y         = to (binop (+) x y)
1469     x - y         = to (binop (-) x y)
1470     negate        = to . negate . from
1471     x * y         = to (binop (*) x y)
1472     abs           = absReal
1473     signum        = signumReal
1474     fromInteger   = to . fromInteger
1475     fromInt       = to
1476
1477 instance Bounded Int16 where
1478     minBound = 0x8000
1479     maxBound = 0x7fff 
1480
1481 instance Real Int16 where
1482     toRational x = toInteger x % 1
1483
1484 instance Integral Int16 where
1485     x `div` y     = to  (binop div x y)
1486     x `quot` y    = to  (binop quot x y)
1487     x `rem` y     = to  (binop rem x y)
1488     x `mod` y     = to  (binop mod x y)
1489     x `quotRem` y = to2 (binop quotRem x y)
1490     even          = even      . from
1491     toInteger     = toInteger . from
1492     toInt         = toInt     . from
1493
1494 instance Ix Int16 where
1495     range (m,n)          = [m..n]
1496     index b@(m,n) i
1497               | inRange b i = from (i - m)
1498               | otherwise   = error "index: Index out of range"
1499     inRange (m,n) i      = m <= i && i <= n
1500
1501 instance Enum Int16 where
1502     toEnum         = to 
1503     fromEnum       = from
1504     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int16)]
1505     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int16)]
1506                           where last = if d < c then minBound else maxBound
1507
1508 instance Read Int16 where
1509     readsPrec p s = [ (to x,r) | (x,r) <- readsPrec p s ]
1510
1511 instance Show Int16 where
1512     showsPrec p = showsPrec p . from
1513
1514 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
1515 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
1516
1517 instance Bits Int16 where
1518   x .&. y       = int32ToInt16 (binop16 (.&.) x y)
1519   x .|. y       = int32ToInt16 (binop16 (.|.) x y)
1520   x `xor` y     = int32ToInt16 (binop16 xor x y)
1521   complement    = int32ToInt16 . complement . int16ToInt32
1522   x `shift` i   = int32ToInt16 (int16ToInt32 x `shift` i)
1523 --  rotate      
1524   bit           = int32ToInt16 . bit
1525   setBit x i    = int32ToInt16 (setBit (int16ToInt32 x) i)
1526   clearBit x i  = int32ToInt16 (clearBit (int16ToInt32 x) i)
1527   complementBit x i = int32ToInt16 (complementBit (int16ToInt32 x) i)
1528   testBit x i   = testBit (int16ToInt32 x) i
1529   bitSize  _    = 16
1530   isSigned _    = True
1531
1532 int16ToInteger = error "TODO: int16ToInteger"
1533 integerToInt16 = error "TODO: integerToInt16"
1534
1535 --intToInt16 = fromInt
1536 --int16ToInt = toInt
1537
1538 sizeofInt16 :: Word32
1539 sizeofInt16 =  2
1540
1541 -----------------------------------------------------------------------------
1542 -- Int32
1543 -----------------------------------------------------------------------------
1544
1545 newtype Int32  = I32 Int
1546
1547 int32ToInt (I32 x) = x
1548 intToInt32 = I32
1549
1550 instance Eq  Int32     where (==)    = binop (==)
1551 instance Ord Int32     where compare = binop compare
1552
1553 instance Num Int32 where
1554     x + y         = to (binop (+) x y)
1555     x - y         = to (binop (-) x y)
1556     negate        = to . negate . from
1557     x * y         = to (binop (*) x y)
1558     abs           = absReal
1559     signum        = signumReal
1560     fromInteger   = to . fromInteger
1561     fromInt       = to
1562
1563 instance Bounded Int32 where
1564     minBound = to minBound
1565     maxBound = to maxBound
1566
1567 instance Real Int32 where
1568     toRational x = toInteger x % 1
1569
1570 instance Integral Int32 where
1571     x `div` y     = to  (binop div x y)
1572     x `quot` y    = to  (binop quot x y)
1573     x `rem` y     = to  (binop rem x y)
1574     x `mod` y     = to  (binop mod x y)
1575     x `quotRem` y = to2 (binop quotRem x y)
1576     even          = even      . from
1577     toInteger     = toInteger . from
1578     toInt         = toInt     . from
1579
1580 instance Ix Int32 where
1581     range (m,n)          = [m..n]
1582     index b@(m,n) i
1583               | inRange b i = from (i - m)
1584               | otherwise   = error "index: Index out of range"
1585     inRange (m,n) i      = m <= i && i <= n
1586
1587 instance Enum Int32 where
1588     toEnum         = to 
1589     fromEnum       = from
1590     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int32)]
1591     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int32)]
1592                           where last = if d < c then minBound else maxBound
1593
1594 instance Read Int32 where
1595     readsPrec p s = [ (to x,r) | (x,r) <- readsPrec p s ]
1596
1597 instance Show Int32 where
1598     showsPrec p = showsPrec p . from
1599
1600 instance Bits Int32 where
1601   (.&.) x y     = to (binop primAndInt x y)
1602   (.|.) x y     = to (binop primOrInt x y)
1603   xor x y       = to (binop primXorInt x y)
1604
1605   complement    = xor ((-1) :: Int32) 
1606   x `shift` i   | i == 0 = x
1607                 | i > 0  = to (primShiftLInt (from x) i)
1608                 | i < 0  = to (primShiftRAInt (from x) (-i))
1609 --  rotate         
1610   bit           = shift 0x1
1611   setBit x i    = x .|. bit i
1612   clearBit x i  = x .&. complement (bit i)
1613   complementBit x i = x `xor` bit i
1614
1615   testBit x i   = (0x1 .&. shift x i) == (0x1 :: Int32)
1616   bitSize  _    = 32
1617   isSigned _    = True
1618
1619
1620 int32ToInteger = error "TODO: int32ToInteger"
1621 integerToInt32 = error "TODO: integerToInt32"
1622
1623 sizeofInt32 :: Word32
1624 sizeofInt32 =  4
1625
1626 -----------------------------------------------------------------------------
1627 -- Int64
1628 --
1629 -- This is not ideal, but does have the advantage that you can 
1630 -- now typecheck generated code that include Int64 statements.
1631 --
1632 -----------------------------------------------------------------------------
1633
1634 type Int64 = Integer
1635
1636 int64ToInteger = error "TODO: int64ToInteger"
1637
1638 integerToInt64 = error "TODO: integerToInt64"
1639
1640 int64ToInt32 = error "TODO: int64ToInt32"
1641 int64ToInt16 = error "TODO: int64ToInt16"
1642 int64ToInt8 = error "TODO: int64ToInt8"
1643
1644 int32ToInt64 = error "TODO: int32ToInt64"
1645 int16ToInt64 = error "TODO: int16ToInt64"
1646 int8ToInt64 = error "TODO: int8ToInt64"
1647
1648 intToInt64 = fromInt
1649 int64ToInt = toInt
1650
1651 sizeofInt64 :: Word32
1652 sizeofInt64 =  8
1653
1654 -----------------------------------------------------------------------------
1655 -- End of exported definitions
1656 --
1657 -- The remainder of this file consists of definitions which are only
1658 -- used in the implementation.
1659 -----------------------------------------------------------------------------
1660
1661 -----------------------------------------------------------------------------
1662 -- Coercions - used to make the instance declarations more uniform
1663 -----------------------------------------------------------------------------
1664
1665 class Coerce a where
1666   to   :: Int -> a
1667   from :: a -> Int
1668
1669 instance Coerce Int32 where
1670   from = int32ToInt
1671   to   = intToInt32
1672
1673 instance Coerce Int8 where
1674   from = int8ToInt
1675   to   = intToInt8
1676
1677 instance Coerce Int16 where
1678   from = int16ToInt
1679   to   = intToInt16
1680
1681 binop :: Coerce int => (Int -> Int -> a) -> (int -> int -> a)
1682 binop op x y = from x `op` from y
1683
1684 to2 :: Coerce int => (Int, Int) -> (int, int)
1685 to2 (x,y) = (to x, to y)
1686
1687 -----------------------------------------------------------------------------
1688 -- Extra primitives
1689 -----------------------------------------------------------------------------
1690
1691 --primitive primAnd "primAndInt" :: Int -> Int -> Int
1692
1693 --primitive primAndInt        :: Int32 -> Int32 -> Int32
1694 --primitive primOrInt         :: Int32 -> Int32 -> Int32
1695 --primitive primXorInt        :: Int32 -> Int32 -> Int32
1696 --primitive primComplementInt :: Int32 -> Int32
1697 --primitive primShiftInt      :: Int32 -> Int -> Int32
1698 --primitive primBitInt        :: Int -> Int32
1699 --primitive primTestInt       :: Int32 -> Int -> Bool
1700
1701 -----------------------------------------------------------------------------
1702 -- Code copied from the Prelude
1703 -----------------------------------------------------------------------------
1704
1705 absReal x    | x >= 0    = x
1706              | otherwise = -x
1707
1708 signumReal x | x == 0    =  0
1709              | x > 0     =  1
1710              | otherwise = -1
1711
1712 -----------------------------------------------------------------------------
1713 -- End
1714 -----------------------------------------------------------------------------
1715
1716 intToWord :: Int -> Word
1717 intToWord i = primIntToWord i
1718
1719 \end{code}
1720 #endif