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