78c694f7384a0ca07f4e091ee7977614820658bb
[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
9 \begin{code}
10 -----------------------------------------------------------------------------
11 -- Signed Integers
12 -- Suitable for use with Hugs 1.4 on 32 bit systems.
13 -----------------------------------------------------------------------------
14
15 module Int
16         ( Int8
17         , Int16
18         , Int32
19         --, Int64
20         , int8ToInt  -- :: Int8  -> Int
21         , intToInt8  -- :: Int   -> Int8
22         , int16ToInt -- :: Int16 -> Int
23         , intToInt16 -- :: Int   -> Int16
24         , int32ToInt -- :: Int32 -> Int
25         , intToInt32 -- :: Int   -> Int32
26         -- plus Eq, Ord, Num, Bounded, Real, Integral, Ix, Enum, Read,
27         --  Show and Bits instances for each of Int8, Int16 and Int32
28         ) where
29
30 import PrelBase
31 import PrelNum
32 import PrelRead
33 import Ix
34 import Bits
35 import PrelGHC
36 import CCall
37
38 -----------------------------------------------------------------------------
39 -- The "official" coercion functions
40 -----------------------------------------------------------------------------
41
42 int8ToInt  :: Int8  -> Int
43 intToInt8  :: Int   -> Int8
44 int16ToInt :: Int16 -> Int
45 intToInt16 :: Int   -> Int16
46 int32ToInt :: Int32 -> Int
47 intToInt32 :: Int   -> Int32
48
49 -- And some non-exported ones
50
51 int8ToInt16  :: Int8  -> Int16
52 int8ToInt32  :: Int8  -> Int32
53 int16ToInt8  :: Int16 -> Int8
54 int16ToInt32 :: Int16 -> Int32
55 int32ToInt8  :: Int32 -> Int8
56 int32ToInt16 :: Int32 -> Int16
57
58 int8ToInt16  (I8#  x) = I16# x
59 int8ToInt32  (I8#  x) = I32# x
60 int16ToInt8  (I16# x) = I8#  x
61 int16ToInt32 (I16# x) = I32# x
62 int32ToInt8  (I32# x) = I8#  x
63 int32ToInt16 (I32# x) = I16# x
64 \end{code}
65
66 \subsection[Int8]{The @Int8@ interface}
67
68 \begin{code}
69 data Int8 = I8# Int#
70 instance CCallable Int8
71 instance CReturnable Int8
72
73 int8ToInt (I8# x) = I# (int8ToInt# x)
74 int8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
75    where x' = word2Int# (int2Word# x `and#` int2Word# 0xff#)
76
77 --
78 -- This doesn't perform any bounds checking
79 -- on the value it is passed, nor its sign.
80 -- i.e., show (intToInt8 511) => "-1"
81 --
82 intToInt8 (I# x) = I8# (intToInt8# x)
83 intToInt8# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xff#)
84
85 instance Eq  Int8     where 
86   (I8# x#) == (I8# y#) = x# ==# y#
87   (I8# x#) /= (I8# y#) = x# /=# y#
88
89 instance Ord Int8 where 
90   compare (I8# x#) (I8# y#) = compareInt# (int8ToInt# x#) (int8ToInt# y#)
91
92 compareInt# :: Int# -> Int# -> Ordering
93 compareInt# x# y#
94  | x# <#  y# = LT
95  | x# ==# y# = EQ
96  | otherwise = GT
97
98 instance Num Int8 where
99   (I8# x#) + (I8# y#) = I8# (intToInt8# (x# +# y#))
100   (I8# x#) - (I8# y#) = I8# (intToInt8# (x# -# y#))
101   (I8# x#) * (I8# y#) = I8# (intToInt8# (x# *# y#))
102   negate i@(I8# x#) = 
103      if x# ==# 0#
104       then i
105       else I8# (0x100# -# x#)
106
107   abs           = absReal
108   signum        = signumReal
109   fromInteger (J# a# s# d#)
110                 = case (integer2Int# a# s# d#) of { i# -> I8# (intToInt8# i#) }
111   fromInt       = intToInt8
112
113 instance Bounded Int8 where
114     minBound = 0x80
115     maxBound = 0x7f 
116
117 instance Real Int8 where
118     toRational x = toInteger x % 1
119
120 instance Integral Int8 where
121     div x@(I8# x#) y@(I8# y#) = 
122        if x > 0 && y < 0        then quotInt8 (x-y-1) y
123        else if x < 0 && y > 0   then quotInt8 (x-y+1) y
124        else quotInt8 x y
125     quot x@(I8# _) y@(I8# y#) =
126        if y# /=# 0#
127        then x `quotInt8` y
128        else error "Integral.Int8.quot: divide by 0\n"
129     rem x@(I8# _) y@(I8# y#) =
130        if y# /=# 0#
131        then x `remInt8` y
132        else error "Integral.Int8.rem: divide by 0\n"
133     mod x@(I8# x#) y@(I8# y#) =
134        if x > 0 && y < 0 || x < 0 && y > 0 then
135           if r/=0 then r+y else 0
136        else
137           r
138         where r = remInt8 x y
139     a@(I8# _) `quotRem` b@(I8# _) = (a `quotInt8` b, a `remInt8` b)
140     toInteger i8  = toInteger (int8ToInt i8)
141     toInt     i8  = int8ToInt i8
142
143 remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `remInt#` (int8ToInt# y)))
144 quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `quotInt#` (int8ToInt# y)))
145
146 instance Ix Int8 where
147     range (m,n)          = [m..n]
148     index b@(m,n) i
149               | inRange b i = int8ToInt (i - m)
150               | otherwise   = error (showString "Ix{Int8}.index: Index " .
151                                      showParen True (showsPrec 0 i) .
152                                      showString " out of range " $
153                                      showParen True (showsPrec 0 b) "")
154     inRange (m,n) i      = m <= i && i <= n
155
156 instance Enum Int8 where
157     toEnum         = intToInt8
158     fromEnum       = int8ToInt
159     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int8)]
160     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int8)]
161                           where last = if d < c then minBound else maxBound
162
163 instance Read Int8 where
164     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
165
166 instance Show Int8 where
167     showsPrec p i8 = showsPrec p (int8ToInt i8)
168
169 binop8 :: (Int32 -> Int32 -> a) -> (Int8 -> Int8 -> a)
170 binop8 op x y = int8ToInt32 x `op` int8ToInt32 y
171
172 instance Bits Int8 where
173   (I8# x) .&. (I8# y) = I8# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
174   (I8# x) .|. (I8# y) = I8# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
175   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
176   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
177   shift (I8# x) i@(I# i#)
178         | i > 0     = I8# (intToInt8# (iShiftL# (int8ToInt# x)  i#))
179         | otherwise = I8# (intToInt8# (iShiftRA# (int8ToInt# x) i#))
180   i8@(I8# x)  `rotate` (I# i)
181         | i ==# 0#    = i8
182         | i ># 0#     = 
183              I8# (intToInt8# ( word2Int#  (
184                      (int2Word# (iShiftL# (int8ToInt# x) i'))
185                              `or#`
186                      (int2Word# (iShiftRA# (word2Int# (
187                                                 (int2Word# x) `and#` 
188                                                 (int2Word# (0x100# -# pow2# i2))))
189                                           i2)))))
190         | otherwise = rotate i8 (I# (8# +# i))
191           where
192            i' = word2Int# (int2Word# i `and#` int2Word# 7#)
193            i2 = 8# -# i'
194   bit i         = shift 1 i
195   setBit x i    = x .|. bit i
196   clearBit x i  = x .&. complement (bit i)
197   complementBit x i = x `xor` bit i
198   testBit x i   = (x .&. bit i) /= 0
199   bitSize  _    = 8
200   isSigned _    = True
201
202 pow2# :: Int# -> Int#
203 pow2# x# = iShiftL# 1# x#
204 \end{code}
205
206 \subsection[Int16]{The @Int16@ interface}
207
208 \begin{code}
209 data Int16  = I16# Int#
210 instance CCallable Int16
211 instance CReturnable Int16
212
213 int16ToInt (I16# x) = I# (int16ToInt# x)
214
215 int16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
216    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
217
218 intToInt16 (I# x) = I16# (intToInt16# x)
219 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
220
221 instance Eq  Int16     where
222   (I16# x#) == (I16# y#) = x# ==# y#
223   (I16# x#) /= (I16# y#) = x# /=# y#
224
225 instance Ord Int16 where
226   compare (I16# x#) (I16# y#) = compareInt# (int16ToInt# x#) (int16ToInt# y#)
227
228 instance Num Int16 where
229   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
230   (I16# x#) - (I16# y#) = I16# (intToInt16# (x# -# y#))
231   (I16# x#) * (I16# y#) = I16# (intToInt16# (x# *# y#))
232   negate i@(I16# x#) = 
233      if x# ==# 0#
234       then i
235       else I16# (0x10000# -# x#)
236   abs           = absReal
237   signum        = signumReal
238   fromInteger (J# a# s# d#)
239                 = case (integer2Int# a# s# d#) of { i# -> I16# (intToInt16# i#) }
240   fromInt       = intToInt16
241
242 instance Bounded Int16 where
243     minBound = 0x8000
244     maxBound = 0x7fff 
245
246 instance Real Int16 where
247     toRational x = toInteger x % 1
248
249 instance Integral Int16 where
250     div x@(I16# x#) y@(I16# y#) = 
251        if x > 0 && y < 0        then quotInt16 (x-y-1) y
252        else if x < 0 && y > 0   then quotInt16 (x-y+1) y
253        else quotInt16 x y
254     quot x@(I16# _) y@(I16# y#) =
255        if y# /=# 0#
256        then x `quotInt16` y
257        else error "Integral.Int16.quot: divide by 0\n"
258     rem x@(I16# _) y@(I16# y#) =
259        if y# /=# 0#
260        then x `remInt16` y
261        else error "Integral.Int16.rem: divide by 0\n"
262     mod x@(I16# x#) y@(I16# y#) =
263        if x > 0 && y < 0 || x < 0 && y > 0 then
264           if r/=0 then r+y else 0
265        else
266           r
267         where r = remInt16 x y
268     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
269     toInteger i16  = toInteger (int16ToInt i16)
270     toInt     i16  = int16ToInt i16
271
272 remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `remInt#` (int16ToInt# y)))
273 quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `quotInt#` (int16ToInt# y)))
274
275 instance Ix Int16 where
276     range (m,n)          = [m..n]
277     index b@(m,n) i
278               | inRange b i = int16ToInt (i - m)
279               | otherwise   = error (showString "Ix{Int16}.index: Index " .
280                                      showParen True (showsPrec 0 i) .
281                                      showString " out of range " $
282                                      showParen True (showsPrec 0 b) "")
283     inRange (m,n) i      = m <= i && i <= n
284
285 instance Enum Int16 where
286     toEnum         = intToInt16
287     fromEnum       = int16ToInt
288     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int16)]
289     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int16)]
290                           where last = if d < c then minBound else maxBound
291
292 instance Read Int16 where
293     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
294
295 instance Show Int16 where
296     showsPrec p i16 = showsPrec p (int16ToInt i16)
297
298 binop16 :: (Int32 -> Int32 -> a) -> (Int16 -> Int16 -> a)
299 binop16 op x y = int16ToInt32 x `op` int16ToInt32 y
300
301 instance Bits Int16 where
302   (I16# x) .&. (I16# y) = I16# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
303   (I16# x) .|. (I16# y) = I16# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
304   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
305   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
306   shift (I16# x) i@(I# i#)
307         | i > 0     = I16# (intToInt16# (iShiftL# (int16ToInt# x)  i#))
308         | otherwise = I16# (intToInt16# (iShiftRA# (int16ToInt# x) i#))
309   i16@(I16# x)  `rotate` (I# i)
310         | i ==# 0#    = i16
311         | i ># 0#     = 
312              I16# (intToInt16# (word2Int# (
313                     (int2Word# (iShiftL# (int16ToInt# x) i')) 
314                              `or#`
315                     (int2Word# (iShiftRA# ( word2Int# (
316                                     (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
317                                           i2)))))
318         | otherwise = rotate i16 (I# (16# +# i))
319           where
320            i' = word2Int# (int2Word# i `and#` int2Word# 15#)
321            i2 = 16# -# i'
322   bit i             = shift 1 i
323   setBit x i        = x .|. bit i
324   clearBit x i      = x .&. complement (bit i)
325   complementBit x i = x `xor` bit i
326   testBit x i       = (x .&. bit i) /= 0
327   bitSize  _        = 16
328   isSigned _        = True
329 \end{code}
330
331 \subsection[Int32]{The @Int32@ interface}
332
333 \begin{code}
334 data Int32  = I32# Int#
335 instance CCallable Int32
336 instance CReturnable Int32
337
338 int32ToInt (I32# x) = I# (int32ToInt# x)
339
340 int32ToInt# :: Int# -> Int#
341 #if WORD_SIZE_IN_BYTES > 4
342 int32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
343    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
344 #else
345 int32ToInt# x = x
346 #endif
347
348 intToInt32 (I# x) = I32# (intToInt32# x)
349 intToInt32# :: Int# -> Int#
350 #if WORD_SIZE_IN_BYTES > 4
351 intToInt32# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffffffff#)
352 #else
353 intToInt32# i# = i#
354 #endif
355
356 instance Eq  Int32     where
357   (I32# x#) == (I32# y#) = x# ==# y#
358   (I32# x#) /= (I32# y#) = x# /=# y#
359
360 instance Ord Int32    where
361   compare (I32# x#) (I32# y#) = compareInt# (int32ToInt# x#) (int32ToInt# y#)
362
363 instance Num Int32 where
364   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
365   (I32# x#) - (I32# y#) = I32# (intToInt32# (x# -# y#))
366   (I32# x#) * (I32# y#) = I32# (intToInt32# (x# *# y#))
367 #if WORD_SIZE_IN_BYTES > 4
368   negate i@(I32# x)  = 
369       if x ==# 0#
370        then i
371        else I32# (intToInt32# (0x100000000# -# x'))
372 #else
373   negate (I32# x)  = I32# (negateInt# x)
374 #endif
375   abs           = absReal
376   signum        = signumReal
377   fromInteger (J# a# s# d#)
378                 = case (integer2Int# a# s# d#) of { i# -> I32# (intToInt32# i#) }
379   fromInt       = intToInt32
380
381 -- ToDo: remove LitLit when minBound::Int is fixed (currently it's one
382 -- too high, and doesn't allow the correct minBound to be defined here).
383 instance Bounded Int32 where 
384     minBound = case ``0x80000000'' of { I# x -> I32# x }
385     maxBound = I32# 0x7fffffff#
386
387 instance Real Int32 where
388     toRational x = toInteger x % 1
389
390 instance Integral Int32 where
391     div x@(I32# x#) y@(I32# y#) = 
392        if x > 0 && y < 0        then quotInt32 (x-y-1) y
393        else if x < 0 && y > 0   then quotInt32 (x-y+1) y
394        else quotInt32 x y
395     quot x@(I32# _) y@(I32# y#) =
396        if y# /=# 0#
397        then x `quotInt32` y
398        else error "Integral.Int32.quot: divide by 0\n"
399     rem x@(I32# _) y@(I32# y#) =
400        if y# /=# 0#
401        then x `remInt32` y
402        else error "Integral.Int32.rem: divide by 0\n"
403     mod x@(I32# x#) y@(I32# y#) =
404        if x > 0 && y < 0 || x < 0 && y > 0 then
405           if r/=0 then r+y else 0
406        else
407           r
408         where r = remInt32 x y
409     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
410     toInteger i32  = toInteger (int32ToInt i32)
411     toInt     i32  = int32ToInt i32
412
413 remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `remInt#` (int32ToInt# y)))
414 quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `quotInt#` (int32ToInt# y)))
415
416 instance Ix Int32 where
417     range (m,n)          = [m..n]
418     index b@(m,n) i
419               | inRange b i = int32ToInt (i - m)
420               | otherwise   = error (showString "Ix{Int32}.index: Index " .
421                                      showParen True (showsPrec 0 i) .
422                                      showString " out of range " $
423                                      showParen True (showsPrec 0 b) "")
424     inRange (m,n) i      = m <= i && i <= n
425
426 instance Enum Int32 where
427     toEnum         = intToInt32
428     fromEnum       = int32ToInt
429     enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int32)]
430     enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int32)]
431                           where last = if d < c then minBound else maxBound
432
433 instance Read Int32 where
434     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
435
436 instance Show Int32 where
437     showsPrec p i32 = showsPrec p (int32ToInt i32)
438
439 instance Bits Int32 where
440   (I32# x) .&. (I32# y)   = I32# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
441   (I32# x) .|. (I32# y)   = I32# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
442   (I32# x) `xor` (I32# y) = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
443 #if WORD_SIZE_IN_BYTES > 4
444   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffffffff#)))
445 #else
446   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
447 #endif
448   shift (I32# x) i@(I# i#)
449         | i > 0     = I32# (intToInt32# (iShiftL# (int32ToInt# x)  i#))
450         | otherwise = I32# (intToInt32# (iShiftRA# (int32ToInt# x) i#))
451   i32@(I32# x)  `rotate` (I# i)
452         | i ==# 0#    = i32
453         | i ># 0#     = 
454              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
455              I32# (intToInt32# ( word2Int# (
456                     (int2Word# (iShiftL# (int32ToInt# x) i')) 
457                           `or#`
458                     (int2Word# (iShiftRA# (word2Int# (
459                                               (int2Word# x) 
460                                                   `and#` 
461                                                (int2Word# (maxBound# -# pow2# i2 +# 1#))))
462                                           i2)))))
463         | otherwise = rotate i32 (I# (32# +# i))
464           where
465            i' = word2Int# (int2Word# i `and#` int2Word# 31#)
466            i2 = 32# -# i'
467            (I32# maxBound#) = maxBound
468   bit i         = shift 1 i
469   setBit x i    = x .|. bit i
470   clearBit x i  = x .&. complement (bit i)
471   complementBit x i = x `xor` bit i
472   testBit x i   = (x .&. bit i) /= 0
473   bitSize  _    = 32
474   isSigned _    = True
475
476 {-# INLINE wordop #-}
477 wordop op (I# x) (I# y) = I# (word2Int# (int2Word# x `op` int2Word# y))
478
479 -----------------------------------------------------------------------------
480 -- End of exported definitions
481 --
482 -- The remainder of this file consists of definitions which are only
483 -- used in the implementation.
484 -----------------------------------------------------------------------------
485
486 -----------------------------------------------------------------------------
487 -- Code copied from the Prelude
488 -----------------------------------------------------------------------------
489
490 absReal x    | x >= 0    = x
491              | otherwise = -x
492
493 signumReal x | x == 0    =  0
494              | x > 0     =  1
495              | otherwise = -1
496 \end{code}