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