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