[project @ 2003-05-05 19:44:28 by ross]
authorross <unknown>
Mon, 5 May 2003 19:44:28 +0000 (19:44 +0000)
committerross <unknown>
Mon, 5 May 2003 19:44:28 +0000 (19:44 +0000)
non-GHC: fill out the Bits instances for Int and Integer, and make them
work with Hugs.

Data/Bits.hs

index 30c687a..25bc9a1 100644 (file)
@@ -42,13 +42,20 @@ module Data.Bits (
 -- See library document for details on the semantics of the
 -- individual operations.
 
-#ifdef __GLASGOW_HASKELL__
+#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
 #include "MachDeps.h"
+#endif
+
+#ifdef __GLASGOW_HASKELL__
 import GHC.Num
 import GHC.Real
 import GHC.Base
 #endif
 
+#ifdef __HUGS__
+import Hugs.Bits
+#endif
+
 infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
 infixl 7 .&.
 infixl 6 `xor`
@@ -88,8 +95,7 @@ class Num a => Bits a where
     {-| Rotate the argument left by the specified number of bits.
        Right rotates are specified by giving a negative value.
 
-        'rotate' is well defined only if 'bitSize' is also well defined
-        ('bitSize' is undefined for 'Integer', for example).
+        For unbounded types like 'Integer', 'rotate' is equivalent to 'shift'.
 
        An instance can define either this unified 'rotate' or 'rotateL' and
        'rotateR', depending on which is more convenient for the type in
@@ -130,7 +136,9 @@ class Num a => Bits a where
     testBit           :: a -> Int -> Bool
 
     {-| Return the number of bits in the type of the argument.  The actual
-        value of the argument is ignored -}
+       value of the argument is ignored.  The function 'bitSize' is
+       undefined for types that do not have a fixed bitsize, like 'Integer'.
+       -}
     bitSize           :: a -> Int
 
     {-| Return 'True' if the argument is a signed type.  The actual
@@ -179,15 +187,15 @@ class Num a => Bits a where
     rotateR           :: a -> Int -> a
     x `rotateR` i = x `rotate` (-i)
 
-#ifdef __GLASGOW_HASKELL__
 instance Bits Int where
+#ifdef __GLASGOW_HASKELL__
     (I# x#) .&.   (I# y#)  = I# (word2Int# (int2Word# x# `and#` int2Word# y#))
     (I# x#) .|.   (I# y#)  = I# (word2Int# (int2Word# x# `or#`  int2Word# y#))
     (I# x#) `xor` (I# y#)  = I# (word2Int# (int2Word# x# `xor#` int2Word# y#))
     complement (I# x#)     = I# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
     (I# x#) `shift` (I# i#)
-        | i# >=# 0#            = I# (x# `iShiftL#` i#)
-        | otherwise            = I# (x# `iShiftRA#` negateInt# i#)
+        | i# >=# 0#        = I# (x# `iShiftL#` i#)
+        | otherwise        = I# (x# `iShiftRA#` negateInt# i#)
     (I# x#) `rotate` (I# i#) =
         I# (word2Int# ((x'# `shiftL#` i'#) `or#`
                        (x'# `shiftRL#` (wsib -# i'#))))
@@ -195,10 +203,51 @@ instance Bits Int where
         x'# = int2Word# x#
         i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
        wsib = WORD_SIZE_IN_BITS#   {- work around preprocessor problem (??) -}
-    bitSize  _                 = WORD_SIZE_IN_BITS
-    isSigned _                 = True
+    bitSize  _             = WORD_SIZE_IN_BITS
+#else /* !__GLASGOW_HASKELL__ */
+
+#ifdef __HUGS__
+    (.&.)                  = primAndInt
+    (.|.)                  = primOrInt
+    xor                    = primXorInt
+    complement             = primComplementInt
+    shift                  = primShiftInt
+    bit                    = primBitInt
+    testBit                = primTestInt
+    bitSize _              = SIZEOF_HSINT*8
+#elif defined(__NHC__)
+    (.&.)                  = nhc_primIntAnd
+    (.|.)                  = nhc_primIntOr
+    xor                    = nhc_primIntXor
+    complement             = nhc_primIntCompl
+    shiftL                 = nhc_primIntLsh
+    shiftR                 = nhc_primIntRsh
+    bitSize _              = 32
+#endif /* __NHC__ */
+
+    x `rotate`  i
+       | i<0 && x<0       = let left = i+bitSize x in
+                             ((x `shift` i) .&. complement ((-1) `shift` left))
+                             .|. (x `shift` left)
+       | i<0              = (x `shift` i) .|. (x `shift` (i+bitSize x))
+       | i==0             = x
+       | i>0              = (x `shift` i) .|. (x `shift` (i-bitSize x))
+
+#endif /* !__GLASGOW_HASKELL__ */
+
+    isSigned _             = True
+
+#ifdef __NHC__
+foreign import ccall nhc_primIntAnd :: Int -> Int -> Int
+foreign import ccall nhc_primIntOr  :: Int -> Int -> Int
+foreign import ccall nhc_primIntXor :: Int -> Int -> Int
+foreign import ccall nhc_primIntLsh :: Int -> Int -> Int
+foreign import ccall nhc_primIntRsh :: Int -> Int -> Int
+foreign import ccall nhc_primIntCompl :: Int -> Int
+#endif /* __NHC__ */
 
 instance Bits Integer where
+#ifdef __GLASGOW_HASKELL__
    (S# x) .&. (S# y) = S# (word2Int# (int2Word# x `and#` int2Word# y))
    x@(S# _) .&. y = toBig x .&. y
    x .&. y@(S# _) = x .&. toBig y
@@ -222,45 +271,60 @@ instance Bits Integer where
    
    complement (S# x) = S# (word2Int# (int2Word# x `xor#` int2Word# (0# -# 1#)))
    complement (J# s d) = case complementInteger# s d of (# s, d #) -> J# s d
+#else
+   -- reduce bitwise binary operations to special cases we can handle
+
+   x .&. y   | x<0 && y<0 = complement (complement x `posOr` complement y)
+            | otherwise  = x `posAnd` y
+   
+   x .|. y   | x<0 || y<0 = complement (complement x `posAnd` complement y)
+            | otherwise  = x `posOr` y
+   
+   x `xor` y | x<0 && y<0 = complement x `posXOr` complement y
+            | x<0        = complement (complement x `posXOr` y)
+            |        y<0 = complement (x `posXOr` complement y)
+            | otherwise  = x `posXOr` y
+
+   -- assuming infinite 2's-complement arithmetic
+   complement a = -1 - a
+#endif
 
    shift x i | i >= 0    = x * 2^i
             | otherwise = x `div` 2^(-i)
 
    rotate x i = shift x i   -- since an Integer never wraps around
 
-   bitSize _  = error "Bits.bitSize(Integer)"
+   bitSize _  = error "Data.Bits.bitSize(Integer)"
    isSigned _ = True
-#endif
-
-#ifdef __NHC__
-instance Bits Int where
-    (.&.)             = nhc_primIntAnd
-    (.|.)             = nhc_primIntOr
-    xor               = nhc_primIntXor
-    complement        = nhc_primIntCompl
-    shiftL            = nhc_primIntLsh
-    shiftR            = nhc_primIntRsh
-    bitSize _         = 32
-    isSigned _        = True
-
-foreign import ccall nhc_primIntAnd :: Int -> Int -> Int
-foreign import ccall nhc_primIntOr  :: Int -> Int -> Int
-foreign import ccall nhc_primIntXor :: Int -> Int -> Int
-foreign import ccall nhc_primIntLsh :: Int -> Int -> Int
-foreign import ccall nhc_primIntRsh :: Int -> Int -> Int
-foreign import ccall nhc_primIntCompl :: Int -> Int
-
-instance Bits Integer where
- -- (.&.) a b          = undefined
- -- (.|.) a b          = undefined
- -- xor a b            = undefined
-    complement a       = (-a)
-    x `shift` i | i<0  = x `div` (2^(-i))
-                | i==0 = x
-                | i>0  = x * (2^i)
-    x `rotate` i       = x `shift` i   -- an Integer never wraps
-    bitSize _          = error "Data.Bits: bitSize :: Integer -> Int"
-    isSigned _         = True
-
-#endif
 
+#ifndef __GLASGOW_HASKELL__
+-- Crude implementation of bitwise operations on Integers: convert them
+-- to finite lists of Ints (least significant first), zip and convert
+-- back again.
+
+-- posAnd requires at least one argument non-negative
+-- posOr and posXOr require both arguments non-negative
+
+posAnd, posOr, posXOr :: Integer -> Integer -> Integer
+posAnd x y   = fromInts $ zipWith (.&.) (toInts x) (toInts y)
+posOr x y    = fromInts $ longZipWith (.|.) (toInts x) (toInts y)
+posXOr x y   = fromInts $ longZipWith xor (toInts x) (toInts y)
+
+longZipWith :: (a -> a -> a) -> [a] -> [a] -> [a]
+longZipWith f xs [] = xs
+longZipWith f [] ys = ys
+longZipWith f (x:xs) (y:ys) = f x y:longZipWith f xs ys
+
+toInts :: Integer -> [Int]
+toInts n
+    | n == 0 = []
+    | otherwise = mkInt (n `mod` numInts):toInts (n `div` numInts)
+  where mkInt n | n > toInteger(maxBound::Int) = fromInteger (n-numInts)
+               | otherwise = fromInteger n
+
+fromInts :: [Int] -> Integer
+fromInts = foldr catInt 0
+    where catInt d n = (if d<0 then n+1 else n)*numInts + toInteger d
+
+numInts = toInteger (maxBound::Int) - toInteger (minBound::Int) + 1
+#endif /* !__GLASGOW_HASKELL__ */