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