[commit: testsuite] master: Test #7689 (de9a545)

Simon Marlow marlowsd at gmail.com
Tue Feb 19 16:57:18 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/de9a5457567313b5890f6aa8caee8f7802464acb

>---------------------------------------------------------------

commit de9a5457567313b5890f6aa8caee8f7802464acb
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Thu Feb 14 13:07:26 2013 +0100

    Test #7689
    
    Tests primitive bitwise `andI#`, `orI#`, `notI#`, `xorI#`
    operations on Int#

>---------------------------------------------------------------

 tests/numeric/should_run/T7689.hs     |   78 +++++++++++++++++++++++++++++++++
 tests/numeric/should_run/T7689.stdout |   37 +++++++++++++++
 tests/numeric/should_run/all.T        |    2 +
 3 files changed, 117 insertions(+), 0 deletions(-)

diff --git a/tests/numeric/should_run/T7689.hs b/tests/numeric/should_run/T7689.hs
new file mode 100644
index 0000000..4f0d8e4
--- /dev/null
+++ b/tests/numeric/should_run/T7689.hs
@@ -0,0 +1,78 @@
+{-# LANGUAGE BangPatterns, MagicHash #-}
+module Main where
+
+import Data.Bits (finiteBitSize)
+import GHC.Exts
+
+main :: IO ()
+main = do
+  -- 0 is the annihilator of andI#
+  print (I# (maxI# `andI#`    0#) == 0)
+  print (I# (minI# `andI#`    0#) == 0)
+  print (I# (0#    `andI#` maxI#) == 0)
+  print (I# (0#    `andI#` minI#) == 0)
+  print (I# (0#    `andI#`    0#) == 0)
+  -- integer with all bits set to 1 is the neutral element of orI#,
+  -- in two's complement this is -1
+  print (I# (maxI# `andI#`   -1#) == maxI)
+  print (I# (minI# `andI#`   -1#) == minI)
+  print (I# (-1#   `andI#` maxI#) == maxI)
+  print (I# (-1#   `andI#` minI#) == minI)
+  print (I# (-1#   `andI#`   -1#) == -1)
+  -- these two numbers have every other bit set, they should give 0
+  print (I# (magicInt1# `andI#` magicInt2#) == 0)
+
+  -- integer with all bits set to 1 is the annihilator of orI#,
+  print (I# (maxI# `orI#`    -1#) == -1)
+  print (I# (minI# `orI#`    -1#) == -1)
+  print (I# (-1#   `orI#`  maxI#) == -1)
+  print (I# (-1#   `orI#`  minI#) == -1)
+  print (I# (-1#   `orI#`    -1#) == -1)
+  -- 0 is the neutral element of orI#
+  print (I# (maxI# `orI#`     0#) == maxI)
+  print (I# (minI# `orI#`     0#) == minI)
+  print (I# (0#    `orI#`  maxI#) == maxI)
+  print (I# (0#    `orI#`  minI#) == minI)
+  print (I# (0#    `orI#`     0#) == 0)
+  -- this time we should get an integer with all bits set, that is -1
+  print (I# (magicInt1# `orI#` magicInt2#) == -1)
+
+  -- suprising as the first two tests may look, this is what we expect from
+  -- bitwise negation in two's complement enccoding
+  print (I# (notI#  0#) == -1)
+  print (I# (notI# -1#) ==  0)
+  -- magic int numbers are bitwise complementary
+  print (I# (notI# magicInt1#) == magicInt2)
+  print (I# (notI# magicInt2#) == magicInt1)
+
+  -- 0 is the identity of xor
+  print (I# (minI# `xorI#`    0#) == minI)
+  print (I# (maxI# `xorI#`    0#) == maxI)
+  print (I# (0#    `xorI#` minI#) == minI)
+  print (I# (0#    `xorI#` maxI#) == maxI)
+  -- anything xored with itself is 0
+  print (I# (maxI# `xorI#` maxI#) == 0)
+  print (I# (minI# `xorI#` minI#) == 0)
+  -- xoring with -1 is like bitwise negation (becuse -1 has all bits set to 1)
+  print (I# (minI# `xorI#`   -1#) == maxI)
+  print (I# (maxI# `xorI#`   -1#) == minI)
+  print (I# (-1#   `xorI#` minI#) == maxI)
+  print (I# (-1#   `xorI#` maxI#) == minI)
+  -- since these two have exactly the opposite bits turned on they should
+  -- give an int with all bits set, and that is -1 as you probably already
+  -- remember by now
+  print (I# (magicInt1# `xorI#` magicInt2#) == -1)
+    where
+      intBitSize = finiteBitSize (undefined :: Int)
+      minI  = minBound :: Int
+      maxI  = maxBound :: Int
+      minI# = x
+          where !(I# x) = minBound
+      maxI# = x
+          where !(I# x) = maxBound
+      magicInt1 = sum $ map (2^) [0,2..intBitSize] :: Int
+      magicInt2 = sum $ map (2^) [1,3..intBitSize] :: Int
+      magicInt1# = x
+          where !(I# x) = magicInt1
+      magicInt2# = x
+          where !(I# x) = magicInt2
diff --git a/tests/numeric/should_run/T7689.stdout b/tests/numeric/should_run/T7689.stdout
new file mode 100644
index 0000000..1a97da1
--- /dev/null
+++ b/tests/numeric/should_run/T7689.stdout
@@ -0,0 +1,37 @@
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
diff --git a/tests/numeric/should_run/all.T b/tests/numeric/should_run/all.T
index 70bd591..747b37f 100644
--- a/tests/numeric/should_run/all.T
+++ b/tests/numeric/should_run/all.T
@@ -60,3 +60,5 @@ test('T7014',
      ['$MAKE -s --no-print-directory T7014'])
 
 test('T7233', normal, compile_and_run, [''])
+
+test('T7689', normal, compile_and_run, [''])





More information about the ghc-commits mailing list