[project @ 1999-02-17 15:57:20 by simonm]
[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         -- The "official" place to get these from is Addr, importing
59         -- them from Int is a non-standard thing to do.
60         , indexInt8OffAddr
61         , indexInt16OffAddr
62         , indexInt32OffAddr
63         , indexInt64OffAddr
64         
65         , readInt8OffAddr
66         , readInt16OffAddr
67         , readInt32OffAddr
68         , readInt64OffAddr
69         
70         , writeInt8OffAddr
71         , writeInt16OffAddr
72         , writeInt32OffAddr
73         , writeInt64OffAddr
74         
75         , sizeofInt8
76         , sizeofInt16
77         , sizeofInt32
78         , sizeofInt64
79         
80         -- The "official" place to get these from is Foreign
81 #ifndef __PARALLEL_HASKELL__
82         , indexInt8OffForeignObj
83         , indexInt16OffForeignObj
84         , indexInt32OffForeignObj
85         , indexInt64OffForeignObj
86
87         , readInt8OffForeignObj
88         , readInt16OffForeignObj
89         , readInt32OffForeignObj
90         , readInt64OffForeignObj
91
92         , writeInt8OffForeignObj
93         , writeInt16OffForeignObj
94         , writeInt32OffForeignObj
95         , writeInt64OffForeignObj
96 #endif
97         
98         -- non-standard, GHC specific
99         , intToWord
100
101         -- Internal, do not use.
102         , int8ToInt#
103         , int16ToInt#
104         , int32ToInt#
105
106         ) where
107
108 #ifdef __HUGS__
109 import PreludeBuiltin
110 #else
111 import PrelBase
112 import CCall
113 import PrelForeign
114 import PrelIOBase
115 import PrelAddr ( Int64(..), Word64(..), Addr(..), Word(..) )
116 #endif
117 import Ix
118 import Bits
119 import Ratio   ( (%) )
120 import Numeric ( readDec )
121 import Word    ( Word32 )
122
123 -----------------------------------------------------------------------------
124 -- The "official" coercion functions
125 -----------------------------------------------------------------------------
126
127 int8ToInt  :: Int8  -> Int
128 int16ToInt :: Int16 -> Int
129 int32ToInt :: Int32 -> Int
130
131 int8ToInt#  :: Int8  -> Int#
132 int16ToInt# :: Int16 -> Int#
133 int32ToInt# :: Int32 -> Int#
134
135 intToInt8  :: Int   -> Int8
136 intToInt16 :: Int   -> Int16
137 intToInt32 :: Int   -> Int32
138
139 int8ToInt16  :: Int8  -> Int16
140 int8ToInt32  :: Int8  -> Int32
141
142 int16ToInt8  :: Int16 -> Int8
143 int16ToInt32 :: Int16 -> Int32
144
145 int32ToInt8  :: Int32 -> Int8
146 int32ToInt16 :: Int32 -> Int16
147
148 int8ToInt16  (I8#  x) = I16# x
149 int8ToInt32  (I8#  x) = I32# x
150 int8ToInt64           = int32ToInt64 . int8ToInt32
151
152 int16ToInt8  (I16# x) = I8#  x
153 int16ToInt32 (I16# x) = I32# x
154 int16ToInt64          = int32ToInt64 . int16ToInt32
155
156 int32ToInt8  (I32# x) = I8#  x
157 int32ToInt16 (I32# x) = I16# x
158
159 --GHC specific
160 intToWord :: Int -> Word
161 intToWord (I# i#) = W# (int2Word# i#)
162 \end{code}
163
164 \subsection[Int8]{The @Int8@ interface}
165
166 \begin{code}
167 data Int8 = I8# Int#
168 instance CCallable Int8
169 instance CReturnable Int8
170
171 int8ToInt (I8# x)  = I# (i8ToInt# x)
172 int8ToInt# (I8# x) = i8ToInt# x
173
174 i8ToInt# :: Int# -> Int#
175 i8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
176    where x' = word2Int# (int2Word# x `and#` int2Word# 0xff#)
177
178 --
179 -- This doesn't perform any bounds checking
180 -- on the value it is passed, nor its sign.
181 -- i.e., show (intToInt8 511) => "-1"
182 --
183 intToInt8 (I# x) = I8# (intToInt8# x)
184
185 intToInt8# :: Int# -> Int#
186 intToInt8# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xff#)
187
188 instance Eq  Int8     where 
189   (I8# x#) == (I8# y#) = x# ==# y#
190   (I8# x#) /= (I8# y#) = x# /=# y#
191
192 instance Ord Int8 where 
193   compare (I8# x#) (I8# y#) = compareInt# (i8ToInt# x#) (i8ToInt# y#)
194
195 compareInt# :: Int# -> Int# -> Ordering
196 compareInt# x# y#
197  | x# <#  y# = LT
198  | x# ==# y# = EQ
199  | otherwise = GT
200
201 instance Num Int8 where
202   (I8# x#) + (I8# y#) = I8# (intToInt8# (x# +# y#))
203   (I8# x#) - (I8# y#) = I8# (intToInt8# (x# -# y#))
204   (I8# x#) * (I8# y#) = I8# (intToInt8# (x# *# y#))
205   negate i@(I8# x#) = 
206      if x# ==# 0#
207       then i
208       else I8# (0x100# -# x#)
209
210   abs           = absReal
211   signum        = signumReal
212   fromInteger (J# s# d#)
213                 = case (integer2Int# s# d#) of { i# -> I8# (intToInt8# i#) }
214   fromInt       = intToInt8
215
216 instance Bounded Int8 where
217     minBound = 0x80
218     maxBound = 0x7f 
219
220 instance Real Int8 where
221     toRational x = toInteger x % 1
222
223 instance Integral Int8 where
224     div x y
225        | x > 0 && y < 0 = quotInt8 (x-y-1) y
226        | x < 0 && y > 0 = quotInt8 (x-y+1) y
227        | otherwise      = quotInt8 x y
228
229     quot x@(I8# _) y@(I8# y#)
230        | y# /=# 0# = x `quotInt8` y
231        | otherwise = divZeroError "quot{Int8}" x
232     rem x@(I8# _) y@(I8# y#)
233        | y# /=# 0#  = x `remInt8` y
234        | otherwise  = divZeroError "rem{Int8}" x
235     mod x y
236        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
237        | otherwise = r
238         where r = remInt8 x y
239
240     a@(I8# _) `quotRem` b@(I8# _) = (a `quotInt8` b, a `remInt8` b)
241     toInteger i8  = toInteger (int8ToInt i8)
242     toInt     i8  = int8ToInt i8
243
244 remInt8, quotInt8 :: Int8 -> Int8 -> Int8
245 remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `remInt#`  (i8ToInt# y)))
246 quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `quotInt#` (i8ToInt# y)))
247
248 instance Ix Int8 where
249     range (m,n)          = [m..n]
250     index b@(m,_) i
251               | inRange b i = int8ToInt (i - m)
252               | otherwise   = indexError i b "Int8"
253     inRange (m,n) i      = m <= i && i <= n
254
255 instance Enum Int8 where
256     succ i
257       | i == maxBound = succError "Int8"
258       | otherwise     = i+1
259     pred i
260       | i == minBound = predError "Int8"
261       | otherwise     = i-1
262
263     toEnum x
264       | x >= toInt (minBound::Int8) && x <= toInt (maxBound::Int8) 
265       = intToInt8 x
266       | otherwise
267       = toEnumError "Int8" x (minBound::Int8,maxBound::Int8)
268
269     fromEnum           = int8ToInt
270     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int8)]
271     enumFromThen e1 e2 = 
272              map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int8)]
273                 where 
274                    last 
275                      | e2 < e1   = minBound
276                      | otherwise = maxBound
277
278 instance Read Int8 where
279     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
280
281 instance Show Int8 where
282     showsPrec p i8 = showsPrec p (int8ToInt i8)
283
284 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
285 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
286
287 instance Bits Int8 where
288   (I8# x) .&. (I8# y) = I8# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
289   (I8# x) .|. (I8# y) = I8# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
290   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
291   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
292   shift (I8# x) i@(I# i#)
293         | i > 0     = I8# (intToInt8# (iShiftL# (i8ToInt# x)  i#))
294         | otherwise = I8# (intToInt8# (iShiftRA# (i8ToInt# x) (negateInt# i#)))
295   i8@(I8# x)  `rotate` (I# i)
296         | i ==# 0#    = i8
297         | i ># 0#     = 
298              I8# (intToInt8# ( word2Int#  (
299                      (int2Word# (iShiftL# (i8ToInt# x) i'))
300                              `or#`
301                      (int2Word# (iShiftRA# (word2Int# (
302                                                 (int2Word# x) `and#` 
303                                                 (int2Word# (0x100# -# pow2# i2))))
304                                           i2)))))
305         | otherwise = rotate i8 (I# (8# +# i))
306           where
307            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
308            i2 = 8# -# i'
309   bit i         = shift 1 i
310   setBit x i    = x .|. bit i
311   clearBit x i  = x .&. complement (bit i)
312   complementBit x i = x `xor` bit i
313   testBit x i   = (x .&. bit i) /= 0
314   bitSize  _    = 8
315   isSigned _    = True
316
317 pow2# :: Int# -> Int#
318 pow2# x# = iShiftL# 1# x#
319
320 pow2_64# :: Int# -> Int64#
321 pow2_64# x# = word64ToInt64# (shiftL64# (wordToWord64# (int2Word# 1#)) x#)
322
323 sizeofInt8 :: Word32
324 sizeofInt8 = 1
325 \end{code}
326
327 \subsection[Int16]{The @Int16@ interface}
328
329 \begin{code}
330 data Int16  = I16# Int#
331 instance CCallable Int16
332 instance CReturnable Int16
333
334 int16ToInt  (I16# x) = I# (i16ToInt# x)
335 int16ToInt# (I16# x) = i16ToInt# x
336
337 i16ToInt# :: Int# -> Int#
338 i16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
339    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
340
341 intToInt16 (I# x) = I16# (intToInt16# x)
342
343 intToInt16# :: Int# -> Int#
344 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
345
346 instance Eq  Int16     where
347   (I16# x#) == (I16# y#) = x# ==# y#
348   (I16# x#) /= (I16# y#) = x# /=# y#
349
350 instance Ord Int16 where
351   compare (I16# x#) (I16# y#) = compareInt# (i16ToInt# x#) (i16ToInt# y#)
352
353 instance Num Int16 where
354   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
355   (I16# x#) - (I16# y#) = I16# (intToInt16# (x# -# y#))
356   (I16# x#) * (I16# y#) = I16# (intToInt16# (x# *# y#))
357   negate i@(I16# x#) = 
358      if x# ==# 0#
359       then i
360       else I16# (0x10000# -# x#)
361   abs           = absReal
362   signum        = signumReal
363   fromInteger (J# s# d#)
364                 = case (integer2Int# s# d#) of { i# -> I16# (intToInt16# i#) }
365   fromInt       = intToInt16
366
367 instance Bounded Int16 where
368     minBound = 0x8000
369     maxBound = 0x7fff 
370
371 instance Real Int16 where
372     toRational x = toInteger x % 1
373
374 instance Integral Int16 where
375     div x y
376        | x > 0 && y < 0 = quotInt16 (x-y-1) y
377        | x < 0 && y > 0 = quotInt16 (x-y+1) y
378        | otherwise      = quotInt16 x y
379
380     quot x@(I16# _) y@(I16# y#)
381        | y# /=# 0#      = x `quotInt16` y
382        | otherwise      = divZeroError "quot{Int16}" x
383     rem x@(I16# _) y@(I16# y#)
384        | y# /=# 0#      = x `remInt16` y
385        | otherwise      = divZeroError "rem{Int16}" x
386     mod x y
387        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
388        | otherwise                        = r
389         where r = remInt16 x y
390
391     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
392     toInteger i16  = toInteger (int16ToInt i16)
393     toInt     i16  = int16ToInt i16
394
395 remInt16, quotInt16 :: Int16 -> Int16 -> Int16
396 remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `remInt#` (i16ToInt# y)))
397 quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `quotInt#` (i16ToInt# y)))
398
399 instance Ix Int16 where
400     range (m,n)          = [m..n]
401     index b@(m,_) i
402               | inRange b i = int16ToInt (i - m)
403               | otherwise   = indexError i b "Int16"
404     inRange (m,n) i      = m <= i && i <= n
405
406 instance Enum Int16 where
407     succ i
408       | i == maxBound = succError "Int16"
409       | otherwise     = i+1
410
411     pred i
412       | i == minBound = predError "Int16"
413       | otherwise     = i-1
414
415     toEnum x
416       | x >= toInt (minBound::Int16) && x <= toInt (maxBound::Int16) 
417       = intToInt16 x
418       | otherwise
419       = toEnumError "Int16" x (minBound::Int16, maxBound::Int16)
420
421     fromEnum         = int16ToInt
422
423     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int16)]
424     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int16)]
425                           where last 
426                                   | e2 < e1   = minBound
427                                   | otherwise = maxBound
428
429 instance Read Int16 where
430     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
431
432 instance Show Int16 where
433     showsPrec p i16 = showsPrec p (int16ToInt i16)
434
435 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
436 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
437
438 instance Bits Int16 where
439   (I16# x) .&. (I16# y) = I16# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
440   (I16# x) .|. (I16# y) = I16# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
441   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
442   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
443   shift (I16# x) i@(I# i#)
444         | i > 0     = I16# (intToInt16# (iShiftL# (i16ToInt# x)  i#))
445         | otherwise = I16# (intToInt16# (iShiftRA# (i16ToInt# x) (negateInt# i#)))
446   i16@(I16# x)  `rotate` (I# i)
447         | i ==# 0#    = i16
448         | i ># 0#     = 
449              I16# (intToInt16# (word2Int# (
450                     (int2Word# (iShiftL# (i16ToInt# x) i')) 
451                              `or#`
452                     (int2Word# (iShiftRA# ( word2Int# (
453                                     (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
454                                           i2)))))
455         | otherwise = rotate i16 (I# (16# +# i))
456           where
457            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
458            i2 = 16# -# i'
459   bit i             = shift 1 i
460   setBit x i        = x .|. bit i
461   clearBit x i      = x .&. complement (bit i)
462   complementBit x i = x `xor` bit i
463   testBit x i       = (x .&. bit i) /= 0
464   bitSize  _        = 16
465   isSigned _        = True
466
467 sizeofInt16 :: Word32
468 sizeofInt16 = 2
469 \end{code}
470
471 %
472 %
473 \subsection[Int32]{The @Int32@ interface}
474 %
475 %
476
477 \begin{code}
478 data Int32  = I32# Int#
479 instance CCallable Int32
480 instance CReturnable Int32
481
482 int32ToInt  (I32# x) = I# (i32ToInt# x)
483 int32ToInt# (I32# x) = i32ToInt# x
484
485 i32ToInt# :: Int# -> Int#
486 #if WORD_SIZE_IN_BYTES > 4
487 i32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
488    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
489 #else
490 i32ToInt# x = x
491 #endif
492
493 intToInt32 (I# x) = I32# (intToInt32# x)
494 intToInt32# :: Int# -> Int#
495 #if WORD_SIZE_IN_BYTES > 4
496 intToInt32# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffffffff#)
497 #else
498 intToInt32# i# = i#
499 #endif
500
501 instance Eq  Int32     where
502   (I32# x#) == (I32# y#) = x# ==# y#
503   (I32# x#) /= (I32# y#) = x# /=# y#
504
505 instance Ord Int32    where
506   compare (I32# x#) (I32# y#) = compareInt# (i32ToInt# x#) (i32ToInt# y#)
507
508 instance Num Int32 where
509   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
510   (I32# x#) - (I32# y#) = I32# (intToInt32# (x# -# y#))
511   (I32# x#) * (I32# y#) = I32# (intToInt32# (x# *# y#))
512 #if WORD_SIZE_IN_BYTES > 4
513   negate i@(I32# x)  = 
514       if x ==# 0#
515        then i
516        else I32# (intToInt32# (0x100000000# -# x'))
517 #else
518   negate (I32# x)  = I32# (negateInt# x)
519 #endif
520   abs           = absReal
521   signum        = signumReal
522   fromInteger (J# s# d#)
523                 = case (integer2Int# s# d#) of { i# -> I32# (intToInt32# i#) }
524   fromInt       = intToInt32
525
526 instance Bounded Int32 where 
527     minBound = fromInt minBound
528     maxBound = fromInt maxBound
529
530 instance Real Int32 where
531     toRational x = toInteger x % 1
532
533 instance Integral Int32 where
534     div x y
535        | x > 0 && y < 0 = quotInt32 (x-y-1) y
536        | x < 0 && y > 0 = quotInt32 (x-y+1) y
537        | otherwise      = quotInt32 x y
538     quot x@(I32# _) y@(I32# y#)
539        | y# /=# 0#  = x `quotInt32` y
540        | otherwise  = divZeroError "quot{Int32}" x
541     rem x@(I32# _) y@(I32# y#)
542        | y# /=# 0#  = x `remInt32` y
543        | otherwise  = divZeroError "rem{Int32}" x
544     mod x y
545        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
546        | otherwise                        = r
547         where r = remInt32 x y
548
549     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
550     toInteger i32  = toInteger (int32ToInt i32)
551     toInt     i32  = int32ToInt i32
552
553 remInt32, quotInt32 :: Int32 -> Int32 -> Int32
554 remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `remInt#` (i32ToInt# y)))
555 quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `quotInt#` (i32ToInt# y)))
556
557 instance Ix Int32 where
558     range (m,n)          = [m..n]
559     index b@(m,_) i
560               | inRange b i = int32ToInt (i - m)
561               | otherwise   = indexError i b "Int32"
562     inRange (m,n) i      = m <= i && i <= n
563
564 instance Enum Int32 where
565     succ i
566       | i == maxBound = succError "Int32"
567       | otherwise     = i+1
568
569     pred i
570       | i == minBound = predError "Int32"
571       | otherwise     = i-1
572
573     toEnum x
574         -- with Int having the same range as Int32, the following test
575         -- shouldn't fail. However, having it here 
576       | x >= toInt (minBound::Int32) && x <= toInt (maxBound::Int32) 
577       = intToInt32 x
578       | otherwise
579       = toEnumError "Int32" x (minBound::Int32, maxBound::Int32)
580
581     fromEnum           = int32ToInt
582
583     enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int32)]
584     enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int32)]
585                           where 
586                             last
587                              | e2 < e1   = minBound
588                              | otherwise = maxBound
589
590 instance Read Int32 where
591     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
592
593 instance Show Int32 where
594     showsPrec p i32 = showsPrec p (int32ToInt i32)
595
596 instance Bits Int32 where
597   (I32# x) .&. (I32# y)   = I32# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
598   (I32# x) .|. (I32# y)   = I32# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
599   (I32# x) `xor` (I32# y) = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
600 #if WORD_SIZE_IN_BYTES > 4
601   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffffffff#)))
602 #else
603   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
604 #endif
605   shift (I32# x) i@(I# i#)
606         | i > 0     = I32# (intToInt32# (iShiftL# (i32ToInt# x)  i#))
607         | otherwise = I32# (intToInt32# (iShiftRA# (i32ToInt# x) (negateInt# i#)))
608   i32@(I32# x)  `rotate` (I# i)
609         | i ==# 0#    = i32
610         | i ># 0#     = 
611              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
612              I32# (intToInt32# ( word2Int# (
613                     (int2Word# (iShiftL# (i32ToInt# x) i')) 
614                           `or#`
615                     (int2Word# (iShiftRA# (word2Int# (
616                                               (int2Word# x) 
617                                                   `and#` 
618                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
619                                           i2)))))
620         | otherwise = rotate i32 (I# (32# +# i))
621           where
622            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
623            i2 = 32# -# i'
624            (I32# maxBound#) = maxBound
625   bit i         = shift 1 i
626   setBit x i    = x .|. bit i
627   clearBit x i  = x .&. complement (bit i)
628   complementBit x i = x `xor` bit i
629   testBit x i   = (x .&. bit i) /= 0
630   bitSize  _    = 32
631   isSigned _    = True
632
633 sizeofInt32 :: Word32
634 sizeofInt32 = 4
635 \end{code}
636
637 \subsection[Int64]{The @Int64@ interface}
638
639
640 \begin{code}
641 #if WORD_SIZE_IN_BYTES == 8
642 --data Int64 = I64# Int#
643
644 int32ToInt64 :: Int32 -> Int64
645 int32ToInt64 (I32# i#) = I64# i#
646
647 intToInt32# :: Int# -> Int#
648 intToInt32# i# = word2Int# ((int2Word# i#) `and#` (case (maxBound::Word32) of W# x# -> x#))
649
650 int64ToInt32 :: Int64 -> Int32
651 int64ToInt32 (I64# i#) = I32# (intToInt32# w#)
652
653 instance Eq  Int64     where 
654   (I64# x) == (I64# y) = x `eqInt#` y
655   (I64# x) /= (I64# y) = x `neInt#` y
656
657 instance Ord Int32    where
658   compare (I64# x#) (I64# y#) = compareInt# x# y#
659
660 instance Num Int64 where
661   (I64# x) + (I64# y) = I64# (x +# y)
662   (I64# x) - (I64# y) = I64# (x -# y)
663   (I64# x) * (I64# y) = I64# (x *# y)
664   negate w@(I64# x)   = I64# (negateInt# x)
665   abs x               = absReal
666   signum              = signumReal
667   fromInteger (J# s# d#) = case (integer2Int# s# d#) of { i# -> I64# i# }
668   fromInt       = intToInt64
669
670 instance Bounded Int64 where
671   minBound = integerToInt64 (-0x8000000000000000)
672   maxBound = integerToInt64 0x7fffffffffffffff
673
674 instance Integral Int64 where
675     div x y
676       | x > 0 && y < 0  = quotInt64 (x-y-1) y
677       | x < 0 && y > 0  = quotInt64 (x-y+1) y
678       | otherwise       = quotInt64 x y
679
680     quot x@(I64# _) y@(I64# y#)
681        | y# /=# 0# = x `quotInt64` y
682        | otherwise = divZeroError "quot{Int64}" x
683
684     rem x@(I64# _) y@(I64# y#)
685        | y# /=# 0# = x `remInt64` y
686        | otherwise = divZeroError "rem{Int64}" x
687
688     mod x y
689        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
690        | otherwise = r
691         where r = remInt64 x y
692
693     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
694     toInteger (I64# i#) = toInteger (I# i#)
695     toInt     (I64# i#) = I# i#
696
697 instance Bits Int64 where
698   (I64# x) .&. (I64# y)   = I64# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
699   (I64# x) .|. (I64# y)   = I64# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
700   (I64# x) `xor` (I64# y) = I64# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
701   complement (I64# x)     = I64# (negateInt# x)
702   shift (I64# x) i@(I# i#)
703         | i > 0     = I64# (iShiftL# x  i#)
704         | otherwise = I64# (iShiftRA# x (negateInt# i#))
705   i64@(I64# x)  `rotate` (I# i)
706         | i ==# 0#    = i64
707         | i ># 0#     = 
708              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
709              I64# (word2Int# (
710                     (int2Word# (iShiftL# x i')) 
711                           `or#`
712                     (int2Word# (iShiftRA# (word2Int# (
713                                               (int2Word# x) 
714                                                   `and#` 
715                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
716                                           i2))))
717         | otherwise = rotate i64 (I# (64# +# i))
718           where
719            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
720            i2 = 64# -# i'
721            (I64# maxBound#) = maxBound
722   bit i         = shift 1 i
723   setBit x i    = x .|. bit i
724   clearBit x i  = x .&. complement (bit i)
725   complementBit x i = x `xor` bit i
726   testBit x i   = (x .&. bit i) /= 0
727   bitSize  _    = 64
728   isSigned _    = True
729
730
731
732 remInt64  (I64# x) (I64# y) = I64# (x `remInt#` y)
733 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt#` y)
734
735 int64ToInteger :: Int64 -> Integer
736 int64ToInteger (I64# i#) = toInteger (I# i#)
737
738 integerToInt64 :: Integer -> Int64
739 integerToInt64 i = case fromInteger i of { I# i# -> I64# i# }
740
741 intToInt64 :: Int -> Int64
742 intToInt64 (I# i#) = I64# i#
743
744 int64ToInt :: Int64 -> Int
745 int64ToInt (I64# i#) = I# i#
746
747 #else
748 --assume: support for long-longs
749 --data Int64 = I64 Int64# deriving (Eq, Ord, Bounded)
750
751 int32ToInt64 :: Int32 -> Int64
752 int32ToInt64 (I32# i#) = I64# (intToInt64# i#)
753
754 int64ToInt32 :: Int64 -> Int32
755 int64ToInt32 (I64# i#) = I32# (int64ToInt# i#)
756
757 int64ToInteger :: Int64 -> Integer
758 int64ToInteger (I64# x#) = 
759    case int64ToInteger# x# of
760      (# s#, p# #) -> J# s# p#
761
762 integerToInt64 :: Integer -> Int64
763 integerToInt64 (J# s# d#) = I64# (integerToInt64# s# d#)
764
765 instance Eq  Int64     where 
766   (I64# x) == (I64# y) = x `eqInt64#` y
767   (I64# x) /= (I64# y) = x `neInt64#` y
768
769 instance Ord Int64     where 
770   compare (I64# x) (I64# y)   = compareInt64# x y
771   (<)  (I64# x) (I64# y)      = x `ltInt64#` y
772   (<=) (I64# x) (I64# y)      = x `leInt64#` y
773   (>=) (I64# x) (I64# y)      = x `geInt64#` y
774   (>)  (I64# x) (I64# y)      = x `gtInt64#` y
775   max x@(I64# x#) y@(I64# y#) = 
776      case (compareInt64# x# y#) of { LT -> y ; EQ -> x ; GT -> x }
777   min x@(I64# x#) y@(I64# y#) =
778      case (compareInt64# x# y#) of { LT -> x ; EQ -> x ; GT -> y }
779
780 instance Num Int64 where
781   (I64# x) + (I64# y) = I64# (x `plusInt64#`  y)
782   (I64# x) - (I64# y) = I64# (x `minusInt64#` y)
783   (I64# x) * (I64# y) = I64# (x `timesInt64#` y)
784   negate (I64# x)     = I64# (negateInt64# x)
785   abs x               = absReal x
786   signum              = signumReal
787   fromInteger i       = integerToInt64 i
788   fromInt     i       = intToInt64 i
789
790 compareInt64# :: Int64# -> Int64# -> Ordering
791 compareInt64# i# j# 
792  | i# `ltInt64#` j# = LT
793  | i# `eqInt64#` j# = EQ
794  | otherwise        = GT
795
796 instance Bounded Int64 where
797   minBound = integerToInt64 (-0x8000000000000000)
798   maxBound = integerToInt64 0x7fffffffffffffff
799
800 instance Integral Int64 where
801     div x y
802       | x > 0 && y < 0  = quotInt64 (x-y-1) y
803       | x < 0 && y > 0  = quotInt64 (x-y+1) y
804       | otherwise       = quotInt64 x y
805
806     quot x@(I64# _) y@(I64# y#)
807        | y# `neInt64#` (intToInt64# 0#) = x `quotInt64` y
808        | otherwise = divZeroError "quot{Int64}" x
809
810     rem x@(I64# _) y@(I64# y#)
811        | y# `neInt64#` (intToInt64# 0#) = x `remInt64` y
812        | otherwise = divZeroError "rem{Int64}" x
813
814     mod x y
815        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
816        | otherwise = r
817         where r = remInt64 x y
818
819     a@(I64# _) `quotRem` b@(I64# _) = (a `quotInt64` b, a `remInt64` b)
820     toInteger i         = int64ToInteger i
821     toInt     i         = int64ToInt i
822
823 instance Bits Int64 where
824   (I64# x) .&. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `and64#` (int64ToWord64# y)))
825   (I64# x) .|. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `or64#`  (int64ToWord64# y)))
826   (I64# x) `xor` (I64# y) = I64# (word64ToInt64# ((int64ToWord64# x) `xor64#` (int64ToWord64# y)))
827   complement (I64# x)     = I64# (negateInt64# x)
828   shift (I64# x) i@(I# i#)
829         | i > 0     = I64# (iShiftL64# x  i#)
830         | otherwise = I64# (iShiftRA64# x (negateInt# i#))
831   i64@(I64# x)  `rotate` (I# i)
832         | i ==# 0#    = i64
833         | i ># 0#     = 
834              -- ( (x<<i') | ((x&(0x10000000000000000-2^i2))>>i2) )
835              I64# (word64ToInt64# (
836                     (int64ToWord64# (iShiftL64# x i'))                    `or64#`
837                     (int64ToWord64# (iShiftRA64# (word64ToInt64# ((int64ToWord64# x)     `and64#` 
838                                                  (int64ToWord64# (maxBound# `minusInt64#` (pow2_64# i2 `plusInt64#` (intToInt64# 1#))))))
839                                                 i2))))
840         | otherwise = rotate i64 (I# (64# +# i))
841           where
842            i' = word2Int# (int2Word# i `and#` int2Word# 63#)
843            i2 = 64# -# i'
844            (I64# maxBound#) = maxBound
845   bit i         = shift 1 i
846   setBit x i    = x .|. bit i
847   clearBit x i  = x .&. complement (bit i)
848   complementBit x i = x `xor` bit i
849   testBit x i   = (x .&. bit i) /= 0
850   bitSize  _    = 64
851   isSigned _    = True
852
853 remInt64, quotInt64 :: Int64 -> Int64 -> Int64
854 remInt64  (I64# x) (I64# y) = I64# (x `remInt64#` y)
855 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt64#` y)
856
857 intToInt64 :: Int -> Int64
858 intToInt64 (I# i#) = I64# (intToInt64# i#)
859
860 int64ToInt :: Int64 -> Int
861 int64ToInt (I64# i#) = I# (int64ToInt# i#)
862
863 -- Word64# primop wrappers:
864
865 ltInt64# :: Int64# -> Int64# -> Bool
866 ltInt64# x# y# =  unsafePerformIO $ do
867         v <- _ccall_ stg_ltInt64 x# y# 
868         case (v::Int) of
869           0 -> return False
870           _ -> return True
871       
872 leInt64# :: Int64# -> Int64# -> Bool
873 leInt64# x# y# =  unsafePerformIO $ do
874         v <- _ccall_ stg_leInt64 x# y# 
875         case (v::Int) of
876           0 -> return False
877           _ -> return True
878       
879 eqInt64# :: Int64# -> Int64# -> Bool
880 eqInt64# x# y# =  unsafePerformIO $ do
881         v <- _ccall_ stg_eqInt64 x# y# 
882         case (v::Int) of
883           0 -> return False
884           _ -> return True
885       
886 neInt64# :: Int64# -> Int64# -> Bool
887 neInt64# x# y# =  unsafePerformIO $ do
888         v <- _ccall_ stg_neInt64 x# y# 
889         case (v::Int) of
890           0 -> return False
891           _ -> return True
892       
893 geInt64# :: Int64# -> Int64# -> Bool
894 geInt64# x# y# =  unsafePerformIO $ do
895         v <- _ccall_ stg_geInt64 x# y# 
896         case (v::Int) of
897           0 -> return False
898           _ -> return True
899       
900 gtInt64# :: Int64# -> Int64# -> Bool
901 gtInt64# x# y# =  unsafePerformIO $ do
902         v <- _ccall_ stg_gtInt64 x# y# 
903         case (v::Int) of
904           0 -> return False
905           _ -> return True
906
907 plusInt64# :: Int64# -> Int64# -> Int64#
908 plusInt64# a# b# = 
909   case (unsafePerformIO (_ccall_ stg_plusInt64 a# b#)) of
910     I64# i# -> i#
911
912 minusInt64# :: Int64# -> Int64# -> Int64#
913 minusInt64# a# b# =
914   case (unsafePerformIO (_ccall_ stg_minusInt64 a# b#)) of
915     I64# i# -> i#
916
917 timesInt64# :: Int64# -> Int64# -> Int64#
918 timesInt64# a# b# =
919   case (unsafePerformIO (_ccall_ stg_timesInt64 a# b#)) of
920     I64# i# -> i#
921
922 quotInt64# :: Int64# -> Int64# -> Int64#
923 quotInt64# a# b# =
924   case (unsafePerformIO (_ccall_ stg_quotInt64 a# b#)) of
925     I64# i# -> i#
926
927 remInt64# :: Int64# -> Int64# -> Int64#
928 remInt64# a# b# =
929   case (unsafePerformIO (_ccall_ stg_remInt64 a# b#)) of
930     I64# i# -> i#
931
932 negateInt64# :: Int64# -> Int64#
933 negateInt64# a# =
934   case (unsafePerformIO (_ccall_ stg_negateInt64 a#)) of
935     I64# i# -> i#
936
937 and64# :: Word64# -> Word64# -> Word64#
938 and64# a# b# =
939   case (unsafePerformIO (_ccall_ stg_and64 a# b#)) of
940     W64# w# -> w#
941
942 or64# :: Word64# -> Word64# -> Word64#
943 or64# a# b# =
944   case (unsafePerformIO (_ccall_ stg_or64 a# b#)) of
945     W64# w# -> w#
946
947 xor64# :: Word64# -> Word64# -> Word64#
948 xor64# a# b# = 
949   case (unsafePerformIO (_ccall_ stg_xor64 a# b#)) of
950     W64# w# -> w#
951
952 not64# :: Word64# -> Word64#
953 not64# a# = 
954   case (unsafePerformIO (_ccall_ stg_not64 a#)) of
955     W64# w# -> w#
956
957 shiftL64# :: Word64# -> Int# -> Word64#
958 shiftL64# a# b# =
959   case (unsafePerformIO (_ccall_ stg_shiftL64 a# b#)) of
960     W64# w# -> w#
961
962 iShiftL64# :: Int64# -> Int# -> Int64#
963 iShiftL64# a# b# =
964   case (unsafePerformIO (_ccall_ stg_iShiftL64 a# b#)) of
965     I64# i# -> i#
966
967 iShiftRL64# :: Int64# -> Int# -> Int64#
968 iShiftRL64# a# b# =
969   case (unsafePerformIO (_ccall_ stg_iShiftRL64 a# b#)) of
970     I64# i# -> i#
971
972 iShiftRA64# :: Int64# -> Int# -> Int64#
973 iShiftRA64# a# b# =
974   case (unsafePerformIO (_ccall_ stg_iShiftRA64 a# b#)) of
975     I64# i# -> i#
976
977 shiftRL64# :: Word64# -> Int# -> Word64#
978 shiftRL64# a# b# =
979   case (unsafePerformIO (_ccall_ stg_shifRtL64 a# b#)) of
980     W64# w# -> w#
981
982 int64ToInt# :: Int64# -> Int#
983 int64ToInt# i64# =
984   case (unsafePerformIO (_ccall_ stg_int64ToInt i64#)) of
985     I# i# -> i#
986
987 wordToWord64# :: Word# -> Word64#
988 wordToWord64# w# =
989   case (unsafePerformIO (_ccall_ stg_wordToWord64 w#)) of
990     W64# w64# -> w64#
991
992 word64ToInt64# :: Word64# -> Int64#
993 word64ToInt64# w# =
994   case (unsafePerformIO (_ccall_ stg_word64ToInt64 w#)) of
995     I64# i# -> i#
996
997 int64ToWord64# :: Int64# -> Word64#
998 int64ToWord64# i# =
999   case (unsafePerformIO (_ccall_ stg_int64ToWord64 i#)) of
1000     W64# w# -> w#
1001
1002 intToInt64# :: Int# -> Int64#
1003 intToInt64# i# =
1004   case (unsafePerformIO (_ccall_ stg_intToInt64 i#)) of
1005     I64# i64# -> i64#
1006
1007 #endif
1008
1009 --
1010 -- Code that's independent of Int64 rep.
1011 -- 
1012 instance Enum Int64 where
1013     succ i
1014       | i == maxBound = succError "Int64"
1015       | otherwise     = i+1
1016
1017     pred i
1018       | i == minBound = predError "Int64"
1019       | otherwise     = i-1
1020
1021     toEnum    i = intToInt64 i
1022     fromEnum  x
1023       | x >= intToInt64 (minBound::Int) && x <= intToInt64 (maxBound::Int)
1024       = int64ToInt x
1025       | otherwise
1026       = fromEnumError "Int64" x
1027
1028     enumFrom e1        = map integerToInt64 [int64ToInteger e1 .. int64ToInteger (maxBound::Int64)]
1029     enumFromTo e1 e2   = map integerToInt64 [int64ToInteger e1 .. int64ToInteger e2]
1030     enumFromThen e1 e2 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger last]
1031                        where 
1032                           last :: Int64
1033                           last 
1034                            | e2 < e1   = minBound
1035                            | otherwise = maxBound
1036
1037     enumFromThenTo e1 e2 e3 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger e3]
1038
1039
1040 instance Show Int64 where
1041     showsPrec p i64 = showsPrec p (int64ToInteger i64)
1042
1043 instance Read Int64 where
1044   readsPrec _ s = [ (integerToInt64 x,r) | (x,r) <- readDec s ]
1045
1046
1047 instance Ix Int64 where
1048     range (m,n)          = [m..n]
1049     index b@(m,_) i
1050            | inRange b i = int64ToInt (i-m)
1051            | otherwise   = indexError i b "Int64"
1052     inRange (m,n) i      = m <= i && i <= n
1053
1054 instance Real Int64 where
1055   toRational x = toInteger x % 1
1056
1057
1058 sizeofInt64 :: Word32
1059 sizeofInt64 = 8
1060
1061 int8ToInteger :: Int8 -> Integer
1062 int8ToInteger i = toInteger i
1063
1064 int16ToInteger :: Int16 -> Integer
1065 int16ToInteger i = toInteger i
1066
1067 int32ToInteger :: Int32 -> Integer
1068 int32ToInteger i = toInteger i
1069
1070 int64ToInt8 :: Int64 -> Int8
1071 int64ToInt8 = int32ToInt8 . int64ToInt32
1072
1073 int64ToInt16 :: Int64 -> Int16
1074 int64ToInt16 = int32ToInt16 . int64ToInt32
1075
1076 integerToInt8 :: Integer -> Int8
1077 integerToInt8 = fromInteger
1078
1079 integerToInt16 :: Integer -> Int16
1080 integerToInt16 = fromInteger
1081
1082 integerToInt32 :: Integer -> Int32
1083 integerToInt32 = fromInteger
1084
1085 \end{code}
1086
1087 %
1088 %
1089 \subsection[Int Utils]{Miscellaneous utilities}
1090 %
1091 %
1092
1093 Code copied from the Prelude
1094
1095 \begin{code}
1096 absReal :: (Ord a, Num a) => a -> a
1097 absReal x    | x >= 0    = x
1098              | otherwise = -x
1099
1100 signumReal :: (Ord a, Num a) => a -> a
1101 signumReal x | x == 0    =  0
1102              | x > 0     =  1
1103              | otherwise = -1
1104 \end{code}
1105
1106 \begin{code}
1107 indexInt8OffAddr  :: Addr -> Int -> Int8
1108 indexInt8OffAddr (A# a#) (I# i#) = intToInt8 (I# (ord# (indexCharOffAddr# a# i#)))
1109
1110 indexInt16OffAddr :: Addr -> Int -> Int16
1111 indexInt16OffAddr a i =
1112 #ifdef WORDS_BIGENDIAN
1113   intToInt16 ( int8ToInt l + (int8ToInt maxBound) * int8ToInt h)
1114 #else
1115   intToInt16 ( int8ToInt h + (int8ToInt maxBound) * int8ToInt l)
1116 #endif
1117  where
1118    byte_idx = i * 2
1119    l = indexInt8OffAddr a byte_idx
1120    h = indexInt8OffAddr a (byte_idx+1)
1121
1122 indexInt32OffAddr :: Addr -> Int -> Int32
1123 indexInt32OffAddr (A# a#) i = intToInt32 (I# (indexIntOffAddr# a# i'#))
1124  where
1125    -- adjust index to be in Int units, not Int32 ones.
1126   (I# i'#) 
1127 #if WORD_SIZE_IN_BYTES==8
1128    = i `div` 2
1129 #else
1130    = i
1131 #endif
1132
1133 indexInt64OffAddr :: Addr -> Int -> Int64
1134 indexInt64OffAddr (A# a#) (I# i#)
1135 #if WORD_SIZE_IN_BYTES==8
1136  = I64# (indexIntOffAddr# a# i#)
1137 #else
1138  = I64# (indexInt64OffAddr# a# i#)
1139 #endif
1140
1141 #ifndef __PARALLEL_HASKELL__
1142
1143 indexInt8OffForeignObj  :: ForeignObj -> Int -> Int8
1144 indexInt8OffForeignObj (ForeignObj fo#) (I# i#) = intToInt8 (I# (ord# (indexCharOffForeignObj# fo# i#)))
1145
1146 indexInt16OffForeignObj :: ForeignObj -> Int -> Int16
1147 indexInt16OffForeignObj fo i =
1148 # ifdef WORDS_BIGENDIAN
1149   intToInt16 ( int8ToInt l + (int8ToInt maxBound) * int8ToInt h)
1150 # else
1151   intToInt16 ( int8ToInt h + (int8ToInt maxBound) * int8ToInt l)
1152 # endif
1153  where
1154    byte_idx = i * 2
1155    l = indexInt8OffForeignObj fo byte_idx
1156    h = indexInt8OffForeignObj fo (byte_idx+1)
1157
1158 indexInt32OffForeignObj :: ForeignObj -> Int -> Int32
1159 indexInt32OffForeignObj (ForeignObj fo#) i = intToInt32 (I# (indexIntOffForeignObj# fo# i'#))
1160  where
1161    -- adjust index to be in Int units, not Int32 ones.
1162   (I# i'#) 
1163 # if WORD_SIZE_IN_BYTES==8
1164    = i `div` 2
1165 # else
1166    = i
1167 # endif
1168
1169 indexInt64OffForeignObj :: ForeignObj -> Int -> Int64
1170 indexInt64OffForeignObj (ForeignObj fo#) (I# i#)
1171 # if WORD_SIZE_IN_BYTES==8
1172  = I64# (indexIntOffForeignObj# fo# i#)
1173 # else
1174  = I64# (indexInt64OffForeignObj# fo# i#)
1175 # endif
1176
1177 #endif /* __PARALLEL_HASKELL__ */
1178 \end{code}
1179
1180 Read words out of mutable memory:
1181
1182 \begin{code}
1183 readInt8OffAddr :: Addr -> Int -> IO Int8
1184 readInt8OffAddr a i = _casm_ `` %r=(StgInt8)(((StgInt8*)%0)[(StgInt)%1]); '' a i
1185
1186 readInt16OffAddr  :: Addr -> Int -> IO Int16
1187 readInt16OffAddr a i = _casm_ `` %r=(StgInt16)(((StgInt16*)%0)[(StgInt)%1]); '' a i
1188
1189 readInt32OffAddr  :: Addr -> Int -> IO Int32
1190 readInt32OffAddr a i = _casm_ `` %r=(StgInt32)(((StgInt32*)%0)[(StgInt)%1]); '' a i
1191
1192 readInt64OffAddr  :: Addr -> Int -> IO Int64
1193 #if WORD_SIZE_IN_BYTES==8
1194 readInt64OffAddr a i = _casm_ `` %r=(StgInt)(((StgInt*)%0)[(StgInt)%1]); '' a i
1195 #else
1196 readInt64OffAddr a i = _casm_ `` %r=(StgInt64)(((StgInt64*)%0)[(StgInt)%1]); '' a i
1197 #endif
1198
1199 #ifndef __PARALLEL_HASKELL__
1200
1201 readInt8OffForeignObj :: ForeignObj -> Int -> IO Int8
1202 readInt8OffForeignObj fo i = _casm_ `` %r=(StgInt8)(((StgInt8*)%0)[(StgInt)%1]); '' fo i
1203
1204 readInt16OffForeignObj  :: ForeignObj -> Int -> IO Int16
1205 readInt16OffForeignObj fo i = _casm_ `` %r=(StgInt16)(((StgInt16*)%0)[(StgInt)%1]); '' fo i
1206
1207 readInt32OffForeignObj  :: ForeignObj -> Int -> IO Int32
1208 readInt32OffForeignObj fo i = _casm_ `` %r=(StgInt32)(((StgInt32*)%0)[(StgInt)%1]); '' fo i
1209
1210 readInt64OffForeignObj  :: ForeignObj -> Int -> IO Int64
1211 # if WORD_SIZE_IN_BYTES==8
1212 readInt64OffForeignObj fo i = _casm_ `` %r=(StgInt)(((StgInt*)%0)[(StgInt)%1]); '' fo i
1213 # else
1214 readInt64OffForeignObj fo i = _casm_ `` %r=(StgInt64)(((StgInt64*)%0)[(StgInt)%1]); '' fo i
1215 # endif
1216
1217 #endif /* __PARALLEL_HASKELL__ */
1218 \end{code}
1219
1220 \begin{code}
1221 writeInt8OffAddr  :: Addr -> Int -> Int8  -> IO ()
1222 writeInt8OffAddr a i e = _casm_ `` (((StgInt8*)%0)[(StgInt)%1])=(StgInt8)%2; '' a i e
1223
1224 writeInt16OffAddr :: Addr -> Int -> Int16 -> IO ()
1225 writeInt16OffAddr a i e = _casm_ `` (((StgInt16*)%0)[(StgInt)%1])=(StgInt16)%2; '' a i e
1226
1227 writeInt32OffAddr :: Addr -> Int -> Int32 -> IO ()
1228 writeInt32OffAddr a i e = _casm_ `` (((StgInt32*)%0)[(StgInt)%1])=(StgInt32)%2; '' a i e
1229
1230 writeInt64OffAddr :: Addr -> Int -> Int64 -> IO ()
1231 #if WORD_SIZE_IN_BYTES==8
1232 writeInt64OffAddr a i e = _casm_ `` (((StgInt*)%0)[(StgInt)%1])=(StgInt)%2; '' a i e
1233 #else
1234 writeInt64OffAddr a i e = _casm_ `` (((StgInt64*)%0)[(StgInt)%1])=(StgInt64)%2; '' a i e
1235 #endif
1236
1237 #ifndef __PARALLEL_HASKELL__
1238
1239 writeInt8OffForeignObj  :: ForeignObj -> Int -> Int8  -> IO ()
1240 writeInt8OffForeignObj fo i e = _casm_ `` (((StgInt8*)%0)[(StgInt)%1])=(StgInt8)%2; '' fo i e
1241
1242 writeInt16OffForeignObj :: ForeignObj -> Int -> Int16 -> IO ()
1243 writeInt16OffForeignObj fo i e = _casm_ `` (((StgInt16*)%0)[(StgInt)%1])=(StgInt16)%2; '' fo i e
1244
1245 writeInt32OffForeignObj :: ForeignObj -> Int -> Int32 -> IO ()
1246 writeInt32OffForeignObj fo i e = _casm_ `` (((StgInt32*)%0)[(StgInt)%1])=(StgInt32)%2; '' fo i e
1247
1248 writeInt64OffForeignObj :: ForeignObj -> Int -> Int64 -> IO ()
1249 # if WORD_SIZE_IN_BYTES==8
1250 writeInt64OffForeignObj fo i e = _casm_ `` (((StgInt*)%0)[(StgInt)%1])=(StgInt)%2; '' fo i e
1251 # else
1252 writeInt64OffForeignObj fo i e = _casm_ `` (((StgInt64*)%0)[(StgInt)%1])=(StgInt64)%2; '' fo i e
1253 # endif
1254
1255 #endif /* __PARALLEL_HASKELL__ */
1256
1257 \end{code}
1258
1259
1260 C&P'ed from Ix.lhs
1261
1262 \begin{code}
1263 {-# NOINLINE indexError #-}
1264 indexError :: Show a => a -> (a,a) -> String -> b
1265 indexError i rng tp
1266   = error (showString "Ix{" . showString tp . showString "}.index: Index " .
1267            showParen True (showsPrec 0 i) .
1268            showString " out of range " $
1269            showParen True (showsPrec 0 rng) "")
1270
1271
1272 toEnumError :: (Show a,Show b) => String -> a -> (b,b) -> c
1273 toEnumError inst_ty tag bnds
1274   = error ("Enum.toEnum{" ++ inst_ty ++ "}: tag " ++
1275            (showParen True (showsPrec 0 tag) $
1276              " is outside of bounds " ++
1277              show bnds))
1278
1279 fromEnumError :: (Show a,Show b) => String -> a -> b
1280 fromEnumError inst_ty tag
1281   = error ("Enum.fromEnum{" ++ inst_ty ++ "}: value " ++
1282            (showParen True (showsPrec 0 tag) $
1283              " is outside of Int's bounds " ++
1284              show (minBound::Int,maxBound::Int)))
1285
1286 succError :: String -> a
1287 succError inst_ty
1288   = error ("Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound")
1289
1290 predError :: String -> a
1291 predError inst_ty
1292   = error ("Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound")
1293
1294 divZeroError :: (Show a) => String -> a -> b
1295 divZeroError meth v 
1296   = error ("Integral." ++ meth ++ ": divide by 0 (" ++ show v ++ " / 0)")
1297
1298 \end{code}