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