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