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