138d668b33d6c524533d6b04da32b83126d0e909
[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         -- non-standard, GHC specific
57         , intToWord
58
59         ) where
60
61 import GlaExts
62 import Ix
63 import Bits
64 import PrelGHC
65 import CCall
66 import Numeric ( readDec )
67 import Word    ( Word32 )
68
69 -----------------------------------------------------------------------------
70 -- The "official" coercion functions
71 -----------------------------------------------------------------------------
72
73 int8ToInt  :: Int8  -> Int
74 intToInt8  :: Int   -> Int8
75 int16ToInt :: Int16 -> Int
76 intToInt16 :: Int   -> Int16
77 int32ToInt :: Int32 -> Int
78 intToInt32 :: Int   -> Int32
79
80 -- And some non-exported ones
81
82 int8ToInt16  :: Int8  -> Int16
83 int8ToInt32  :: Int8  -> Int32
84 int16ToInt8  :: Int16 -> Int8
85 int16ToInt32 :: Int16 -> Int32
86 int32ToInt8  :: Int32 -> Int8
87 int32ToInt16 :: Int32 -> Int16
88
89 int8ToInt16  (I8#  x) = I16# x
90 int8ToInt32  (I8#  x) = I32# x
91 int16ToInt8  (I16# x) = I8#  x
92 int16ToInt32 (I16# x) = I32# x
93 int32ToInt8  (I32# x) = I8#  x
94 int32ToInt16 (I32# x) = I16# x
95
96 --GHC specific
97 intToWord :: Int -> Word
98 intToWord (I# i#) = W# (int2Word# i#)
99 \end{code}
100
101 \subsection[Int8]{The @Int8@ interface}
102
103 \begin{code}
104 data Int8 = I8# Int#
105 instance CCallable Int8
106 instance CReturnable Int8
107
108 int8ToInt (I8# x) = I# (int8ToInt# x)
109 int8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
110    where x' = word2Int# (int2Word# x `and#` int2Word# 0xff#)
111
112 --
113 -- This doesn't perform any bounds checking
114 -- on the value it is passed, nor its sign.
115 -- i.e., show (intToInt8 511) => "-1"
116 --
117 intToInt8 (I# x) = I8# (intToInt8# x)
118 intToInt8# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xff#)
119
120 instance Eq  Int8     where 
121   (I8# x#) == (I8# y#) = x# ==# y#
122   (I8# x#) /= (I8# y#) = x# /=# y#
123
124 instance Ord Int8 where 
125   compare (I8# x#) (I8# y#) = compareInt# (int8ToInt# x#) (int8ToInt# y#)
126
127 compareInt# :: Int# -> Int# -> Ordering
128 compareInt# x# y#
129  | x# <#  y# = LT
130  | x# ==# y# = EQ
131  | otherwise = GT
132
133 instance Num Int8 where
134   (I8# x#) + (I8# y#) = I8# (intToInt8# (x# +# y#))
135   (I8# x#) - (I8# y#) = I8# (intToInt8# (x# -# y#))
136   (I8# x#) * (I8# y#) = I8# (intToInt8# (x# *# y#))
137   negate i@(I8# x#) = 
138      if x# ==# 0#
139       then i
140       else I8# (0x100# -# x#)
141
142   abs           = absReal
143   signum        = signumReal
144   fromInteger (J# a# s# d#)
145                 = case (integer2Int# a# s# d#) of { i# -> I8# (intToInt8# i#) }
146   fromInt       = intToInt8
147
148 instance Bounded Int8 where
149     minBound = 0x80
150     maxBound = 0x7f 
151
152 instance Real Int8 where
153     toRational x = toInteger x % 1
154
155 instance Integral Int8 where
156     div x@(I8# x#) y@(I8# y#) = 
157        if x > 0 && y < 0        then quotInt8 (x-y-1) y
158        else if x < 0 && y > 0   then quotInt8 (x-y+1) y
159        else quotInt8 x y
160     quot x@(I8# _) y@(I8# y#) =
161        if y# /=# 0#
162        then x `quotInt8` y
163        else error "Integral.Int8.quot: divide by 0\n"
164     rem x@(I8# _) y@(I8# y#) =
165        if y# /=# 0#
166        then x `remInt8` y
167        else error "Integral.Int8.rem: divide by 0\n"
168     mod x@(I8# x#) y@(I8# y#) =
169        if x > 0 && y < 0 || x < 0 && y > 0 then
170           if r/=0 then r+y else 0
171        else
172           r
173         where r = remInt8 x y
174     a@(I8# _) `quotRem` b@(I8# _) = (a `quotInt8` b, a `remInt8` b)
175     toInteger i8  = toInteger (int8ToInt i8)
176     toInt     i8  = int8ToInt i8
177
178 remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `remInt#` (int8ToInt# y)))
179 quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `quotInt#` (int8ToInt# y)))
180
181 instance Ix Int8 where
182     range (m,n)          = [m..n]
183     index b@(m,n) i
184               | inRange b i = int8ToInt (i - m)
185               | otherwise   = error (showString "Ix{Int8}.index: Index " .
186                                      showParen True (showsPrec 0 i) .
187                                      showString " out of range " $
188                                      showParen True (showsPrec 0 b) "")
189     inRange (m,n) i      = m <= i && i <= n
190
191 instance Enum Int8 where
192     toEnum         = intToInt8
193     fromEnum       = int8ToInt
194     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int8)]
195     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int8)]
196                           where last = if d < c then minBound else maxBound
197
198 instance Read Int8 where
199     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
200
201 instance Show Int8 where
202     showsPrec p i8 = showsPrec p (int8ToInt i8)
203
204 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
205 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
206
207 instance Bits Int8 where
208   (I8# x) .&. (I8# y) = I8# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
209   (I8# x) .|. (I8# y) = I8# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
210   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
211   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
212   shift (I8# x) i@(I# i#)
213         | i > 0     = I8# (intToInt8# (iShiftL# (int8ToInt# x)  i#))
214         | otherwise = I8# (intToInt8# (iShiftRA# (int8ToInt# x) (negateInt# i#)))
215   i8@(I8# x)  `rotate` (I# i)
216         | i ==# 0#    = i8
217         | i ># 0#     = 
218              I8# (intToInt8# ( word2Int#  (
219                      (int2Word# (iShiftL# (int8ToInt# x) i'))
220                              `or#`
221                      (int2Word# (iShiftRA# (word2Int# (
222                                                 (int2Word# x) `and#` 
223                                                 (int2Word# (0x100# -# pow2# i2))))
224                                           i2)))))
225         | otherwise = rotate i8 (I# (8# +# i))
226           where
227            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
228            i2 = 8# -# i'
229   bit i         = shift 1 i
230   setBit x i    = x .|. bit i
231   clearBit x i  = x .&. complement (bit i)
232   complementBit x i = x `xor` bit i
233   testBit x i   = (x .&. bit i) /= 0
234   bitSize  _    = 8
235   isSigned _    = True
236
237 pow2# :: Int# -> Int#
238 pow2# x# = iShiftL# 1# x#
239
240 sizeofInt8 :: Word32
241 sizeofInt8 = 1
242 \end{code}
243
244 \subsection[Int16]{The @Int16@ interface}
245
246 \begin{code}
247 data Int16  = I16# Int#
248 instance CCallable Int16
249 instance CReturnable Int16
250
251 int16ToInt (I16# x) = I# (int16ToInt# x)
252
253 int16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
254    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
255
256 intToInt16 (I# x) = I16# (intToInt16# x)
257 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
258
259 instance Eq  Int16     where
260   (I16# x#) == (I16# y#) = x# ==# y#
261   (I16# x#) /= (I16# y#) = x# /=# y#
262
263 instance Ord Int16 where
264   compare (I16# x#) (I16# y#) = compareInt# (int16ToInt# x#) (int16ToInt# y#)
265
266 instance Num Int16 where
267   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
268   (I16# x#) - (I16# y#) = I16# (intToInt16# (x# -# y#))
269   (I16# x#) * (I16# y#) = I16# (intToInt16# (x# *# y#))
270   negate i@(I16# x#) = 
271      if x# ==# 0#
272       then i
273       else I16# (0x10000# -# x#)
274   abs           = absReal
275   signum        = signumReal
276   fromInteger (J# a# s# d#)
277                 = case (integer2Int# a# s# d#) of { i# -> I16# (intToInt16# i#) }
278   fromInt       = intToInt16
279
280 instance Bounded Int16 where
281     minBound = 0x8000
282     maxBound = 0x7fff 
283
284 instance Real Int16 where
285     toRational x = toInteger x % 1
286
287 instance Integral Int16 where
288     div x@(I16# x#) y@(I16# y#) = 
289        if x > 0 && y < 0        then quotInt16 (x-y-1) y
290        else if x < 0 && y > 0   then quotInt16 (x-y+1) y
291        else quotInt16 x y
292     quot x@(I16# _) y@(I16# y#) =
293        if y# /=# 0#
294        then x `quotInt16` y
295        else error "Integral.Int16.quot: divide by 0\n"
296     rem x@(I16# _) y@(I16# y#) =
297        if y# /=# 0#
298        then x `remInt16` y
299        else error "Integral.Int16.rem: divide by 0\n"
300     mod x@(I16# x#) y@(I16# y#) =
301        if x > 0 && y < 0 || x < 0 && y > 0 then
302           if r/=0 then r+y else 0
303        else
304           r
305         where r = remInt16 x y
306     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
307     toInteger i16  = toInteger (int16ToInt i16)
308     toInt     i16  = int16ToInt i16
309
310 remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `remInt#` (int16ToInt# y)))
311 quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `quotInt#` (int16ToInt# y)))
312
313 instance Ix Int16 where
314     range (m,n)          = [m..n]
315     index b@(m,n) i
316               | inRange b i = int16ToInt (i - m)
317               | otherwise   = error (showString "Ix{Int16}.index: Index " .
318                                      showParen True (showsPrec 0 i) .
319                                      showString " out of range " $
320                                      showParen True (showsPrec 0 b) "")
321     inRange (m,n) i      = m <= i && i <= n
322
323 instance Enum Int16 where
324     toEnum         = intToInt16
325     fromEnum       = int16ToInt
326     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int16)]
327     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int16)]
328                           where last = if d < c then minBound else maxBound
329
330 instance Read Int16 where
331     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
332
333 instance Show Int16 where
334     showsPrec p i16 = showsPrec p (int16ToInt i16)
335
336 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
337 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
338
339 instance Bits Int16 where
340   (I16# x) .&. (I16# y) = I16# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
341   (I16# x) .|. (I16# y) = I16# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
342   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
343   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
344   shift (I16# x) i@(I# i#)
345         | i > 0     = I16# (intToInt16# (iShiftL# (int16ToInt# x)  i#))
346         | otherwise = I16# (intToInt16# (iShiftRA# (int16ToInt# x) (negateInt# i#)))
347   i16@(I16# x)  `rotate` (I# i)
348         | i ==# 0#    = i16
349         | i ># 0#     = 
350              I16# (intToInt16# (word2Int# (
351                     (int2Word# (iShiftL# (int16ToInt# x) i')) 
352                              `or#`
353                     (int2Word# (iShiftRA# ( word2Int# (
354                                     (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
355                                           i2)))))
356         | otherwise = rotate i16 (I# (16# +# i))
357           where
358            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
359            i2 = 16# -# i'
360   bit i             = shift 1 i
361   setBit x i        = x .|. bit i
362   clearBit x i      = x .&. complement (bit i)
363   complementBit x i = x `xor` bit i
364   testBit x i       = (x .&. bit i) /= 0
365   bitSize  _        = 16
366   isSigned _        = True
367
368 sizeofInt16 :: Word32
369 sizeofInt16 = 2
370 \end{code}
371
372 %
373 %
374 \subsection[Int32]{The @Int32@ interface}
375 %
376 %
377
378 \begin{code}
379 data Int32  = I32# Int#
380 instance CCallable Int32
381 instance CReturnable Int32
382
383 int32ToInt (I32# x) = I# (int32ToInt# x)
384
385 int32ToInt# :: Int# -> Int#
386 #if WORD_SIZE_IN_BYTES > 4
387 int32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
388    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
389 #else
390 int32ToInt# x = x
391 #endif
392
393 intToInt32 (I# x) = I32# (intToInt32# x)
394 intToInt32# :: Int# -> Int#
395 #if WORD_SIZE_IN_BYTES > 4
396 intToInt32# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffffffff#)
397 #else
398 intToInt32# i# = i#
399 #endif
400
401 instance Eq  Int32     where
402   (I32# x#) == (I32# y#) = x# ==# y#
403   (I32# x#) /= (I32# y#) = x# /=# y#
404
405 instance Ord Int32    where
406   compare (I32# x#) (I32# y#) = compareInt# (int32ToInt# x#) (int32ToInt# y#)
407
408 instance Num Int32 where
409   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
410   (I32# x#) - (I32# y#) = I32# (intToInt32# (x# -# y#))
411   (I32# x#) * (I32# y#) = I32# (intToInt32# (x# *# y#))
412 #if WORD_SIZE_IN_BYTES > 4
413   negate i@(I32# x)  = 
414       if x ==# 0#
415        then i
416        else I32# (intToInt32# (0x100000000# -# x'))
417 #else
418   negate (I32# x)  = I32# (negateInt# x)
419 #endif
420   abs           = absReal
421   signum        = signumReal
422   fromInteger (J# a# s# d#)
423                 = case (integer2Int# a# s# d#) of { i# -> I32# (intToInt32# i#) }
424   fromInt       = intToInt32
425
426 -- ToDo: remove LitLit when minBound::Int is fixed (currently it's one
427 -- too high, and doesn't allow the correct minBound to be defined here).
428 instance Bounded Int32 where 
429     minBound = case ``0x80000000'' of { I# x -> I32# x }
430     maxBound = I32# 0x7fffffff#
431
432 instance Real Int32 where
433     toRational x = toInteger x % 1
434
435 instance Integral Int32 where
436     div x@(I32# x#) y@(I32# y#) = 
437        if x > 0 && y < 0        then quotInt32 (x-y-1) y
438        else if x < 0 && y > 0   then quotInt32 (x-y+1) y
439        else quotInt32 x y
440     quot x@(I32# _) y@(I32# y#) =
441        if y# /=# 0#
442        then x `quotInt32` y
443        else error "Integral.Int32.quot: divide by 0\n"
444     rem x@(I32# _) y@(I32# y#) =
445        if y# /=# 0#
446        then x `remInt32` y
447        else error "Integral.Int32.rem: divide by 0\n"
448     mod x@(I32# x#) y@(I32# y#) =
449        if x > 0 && y < 0 || x < 0 && y > 0 then
450           if r/=0 then r+y else 0
451        else
452           r
453         where r = remInt32 x y
454     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
455     toInteger i32  = toInteger (int32ToInt i32)
456     toInt     i32  = int32ToInt i32
457
458 remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `remInt#` (int32ToInt# y)))
459 quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `quotInt#` (int32ToInt# y)))
460
461 instance Ix Int32 where
462     range (m,n)          = [m..n]
463     index b@(m,n) i
464               | inRange b i = int32ToInt (i - m)
465               | otherwise   = error (showString "Ix{Int32}.index: Index " .
466                                      showParen True (showsPrec 0 i) .
467                                      showString " out of range " $
468                                      showParen True (showsPrec 0 b) "")
469     inRange (m,n) i      = m <= i && i <= n
470
471 instance Enum Int32 where
472     toEnum         = intToInt32
473     fromEnum       = int32ToInt
474     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int32)]
475     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int32)]
476                           where last = if d < c then minBound else maxBound
477
478 instance Read Int32 where
479     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
480
481 instance Show Int32 where
482     showsPrec p i32 = showsPrec p (int32ToInt i32)
483
484 instance Bits Int32 where
485   (I32# x) .&. (I32# y)   = I32# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
486   (I32# x) .|. (I32# y)   = I32# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
487   (I32# x) `xor` (I32# y) = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
488 #if WORD_SIZE_IN_BYTES > 4
489   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffffffff#)))
490 #else
491   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
492 #endif
493   shift (I32# x) i@(I# i#)
494         | i > 0     = I32# (intToInt32# (iShiftL# (int32ToInt# x)  i#))
495         | otherwise = I32# (intToInt32# (iShiftRA# (int32ToInt# x) (negateInt# i#)))
496   i32@(I32# x)  `rotate` (I# i)
497         | i ==# 0#    = i32
498         | i ># 0#     = 
499              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
500              I32# (intToInt32# ( word2Int# (
501                     (int2Word# (iShiftL# (int32ToInt# x) i')) 
502                           `or#`
503                     (int2Word# (iShiftRA# (word2Int# (
504                                               (int2Word# x) 
505                                                   `and#` 
506                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
507                                           i2)))))
508         | otherwise = rotate i32 (I# (32# +# i))
509           where
510            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
511            i2 = 32# -# i'
512            (I32# maxBound#) = maxBound
513   bit i         = shift 1 i
514   setBit x i    = x .|. bit i
515   clearBit x i  = x .&. complement (bit i)
516   complementBit x i = x `xor` bit i
517   testBit x i   = (x .&. bit i) /= 0
518   bitSize  _    = 32
519   isSigned _    = True
520
521 sizeofInt32 :: Word32
522 sizeofInt32 = 4
523 \end{code}
524
525 \subsection[Int64]{The @Int64@ interface}
526
527
528 \begin{code}
529 data Int64 = I64 {lo,hi::Int32} deriving (Eq, Ord, Bounded)
530
531 int64ToInteger :: Int64 -> Integer
532 int64ToInteger I64{lo,hi} = toInteger lo + 0x100000000 * toInteger hi 
533
534 integerToInt64 :: Integer -> Int64
535 integerToInt64 x = case x `quotRem` 0x100000000 of 
536                  (h,l) -> I64{lo=fromInteger l, hi=fromInteger h}
537
538 intToInt64 :: Int -> Int64
539 intToInt64 x =  I64{lo=intToInt32 x, hi=0}
540
541 int64ToInt :: Int64 -> Int
542 int64ToInt (I64 lo _) = int32ToInt lo
543
544 instance Show Int64 where
545   showsPrec p x = showsPrec p (int64ToInteger x)
546
547 instance Read Int64 where
548   readsPrec p s = [ (integerToInt64 x,r) | (x,r) <- readDec s ]
549
550 sizeofInt64 :: Word32
551 sizeofInt64 = 8
552 \end{code}
553
554 %
555 %
556 \subsection[Int Utils]{Miscellaneous utilities}
557 %
558 %
559
560 Code copied from the Prelude
561
562 \begin{code}
563 absReal x    | x >= 0    = x
564              | otherwise = -x
565
566 signumReal x | x == 0    =  0
567              | x > 0     =  1
568              | otherwise = -1
569 \end{code}
570
571 \begin{code}
572 indexInt8OffAddr  :: Addr -> Int -> Int8
573 indexInt8OffAddr (A# a#) (I# i#) = intToInt8 (I# (ord# (indexCharOffAddr# a# i#)))
574
575 indexInt16OffAddr :: Addr -> Int -> Int16
576 indexInt16OffAddr a i =
577 #ifdef WORDS_BIGENDIAN
578   intToInt16 ( int8ToInt l + (int8ToInt maxBound) * int8ToInt h)
579 #else
580   intToInt16 ( int8ToInt h + (int8ToInt maxBound) * int8ToInt l)
581 #endif
582  where
583    byte_idx = i * 2
584    l = indexInt8OffAddr a byte_idx
585    h = indexInt8OffAddr a (byte_idx+1)
586
587 indexInt32OffAddr :: Addr -> Int -> Int32
588 indexInt32OffAddr (A# a#) i = intToInt32 (I# (indexIntOffAddr# a# i'#))
589  where
590    -- adjust index to be in Int units, not Int32 ones.
591   (I# i'#) 
592 #if WORD_SIZE_IN_BYTES==8
593    = i `div` 2
594 #else
595    = i
596 #endif
597
598 indexInt64OffAddr :: Addr -> Int -> Int64
599 indexInt64OffAddr (A# i#)
600 #if WORD_SIZE_IN_BYTES==8
601  = I64# (indexIntOffAddr# a# i#)
602 #else
603  = error "Int.indexInt64OffAddr: not implemented yet"
604 #endif
605
606 \end{code}
607
608 Read words out of mutable memory:
609
610 \begin{code}
611 readInt8OffAddr :: Addr -> Int -> IO Int8
612 readInt8OffAddr a i = _casm_ `` %r=(StgInt8)(((StgInt8*)%0)[(StgInt)%1]); '' a i
613
614 readInt16OffAddr  :: Addr -> Int -> IO Int16
615 readInt16OffAddr a i = _casm_ `` %r=(StgInt16)(((StgInt16*)%0)[(StgInt)%1]); '' a i
616
617 readInt32OffAddr  :: Addr -> Int -> IO Int32
618 readInt32OffAddr a i = _casm_ `` %r=(StgInt32)(((StgInt32*)%0)[(StgInt)%1]); '' a i
619
620 readInt64OffAddr  :: Addr -> Int -> IO Int64
621 #if WORD_SIZE_IN_BYTES==8
622 readInt64OffAddr a i = _casm_ `` %r=(StgInt)(((StgInt*)%0)[(StgInt)%1]); '' a i
623 #else
624 readInt64OffAddr a i = error "Int.readInt64OffAddr: not implemented yet"
625 #endif
626 \end{code}
627
628 \begin{code}
629 writeInt8OffAddr  :: Addr -> Int -> Int8  -> IO ()
630 writeInt8OffAddr a i e = _casm_ `` (((StgInt8*)%0)[(StgInt)%1])=(StgInt8)%2; '' a i e
631
632 writeInt16OffAddr :: Addr -> Int -> Int16 -> IO ()
633 writeInt16OffAddr a i e = _casm_ `` (((StgInt16*)%0)[(StgInt)%1])=(StgInt16)%2; '' a i e
634
635 writeInt32OffAddr :: Addr -> Int -> Int32 -> IO ()
636 writeInt32OffAddr a i e = _casm_ `` (((StgInt32*)%0)[(StgInt)%1])=(StgInt32)%2; '' a i e
637
638 writeInt64OffAddr :: Addr -> Int -> Int64 -> IO ()
639 #if WORD_SIZE_IN_BYTES==8
640 writeInt64OffAddr a i e = _casm_ `` (((StgInt*)%0)[(StgInt)%1])=(StgInt)%2; '' a i e
641 #else
642 writeInt64OffAddr = error "Int.writeInt64OffAddr: not implemented yet"
643 #endif
644
645 \end{code}
646