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