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