[commit: ghc] master: Add testcase for getSizeofMutableByteArray# (11778f7)

git at git.haskell.org git at git.haskell.org
Sun Dec 27 17:47:03 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/11778f74da669b13e3748191e89e3c3cafed903b/ghc

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

commit 11778f74da669b13e3748191e89e3c3cafed903b
Author: Ben Gamari <bgamari at smart-cactus.org>
Date:   Sun Dec 27 17:49:03 2015 +0100

    Add testcase for getSizeofMutableByteArray#
    
    In an attempt to track down #11296. Unfortunately the primop appears
    to be working as expected.
    
    Test Plan: validate
    
    Reviewers: hvr, austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1706
    
    GHC Trac Issues: #11296


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

11778f74da669b13e3748191e89e3c3cafed903b
 testsuite/tests/primops/should_run/T11296.hs       | 30 ++++++++++++++++++++++
 .../tests/primops/should_run/T11296.stdout         |  0
 testsuite/tests/primops/should_run/all.T           |  1 +
 3 files changed, 31 insertions(+)

diff --git a/testsuite/tests/primops/should_run/T11296.hs b/testsuite/tests/primops/should_run/T11296.hs
new file mode 100644
index 0000000..c487974
--- /dev/null
+++ b/testsuite/tests/primops/should_run/T11296.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+
+import Control.Monad (unless)
+import GHC.Exts
+import GHC.Types
+
+data ByteArray s = BA (MutableByteArray# s)
+
+main :: IO ()
+main = do
+    ba# <- IO (\s0 -> case newByteArray# 256# s0 of
+                        (# s1, ba# #) -> (# s1, BA ba# #))
+    let go n = do
+            shrink ba# n
+            sz <- getSize ba#
+            unless (sz == n) $ print (sz, n)
+    mapM go [128, 64, 63, 32, 2, 1]
+    return ()
+
+shrink :: ByteArray RealWorld -> Int -> IO ()
+shrink (BA ba#) (I# n#) = IO (\s ->
+    case shrinkMutableByteArray# ba# n# s of
+      s' -> (# s', () #))
+
+getSize :: ByteArray RealWorld -> IO Int
+getSize (BA ba#) = IO (\s ->
+    case getSizeofMutableByteArray# ba# s of
+      (# s', n# #) -> (# s', I# n# #))
+
diff --git a/libraries/base/tests/IO/misc001.stdout b/testsuite/tests/primops/should_run/T11296.stdout
similarity index 100%
copy from libraries/base/tests/IO/misc001.stdout
copy to testsuite/tests/primops/should_run/T11296.stdout
diff --git a/testsuite/tests/primops/should_run/all.T b/testsuite/tests/primops/should_run/all.T
index 2003fc3..68a2d56 100644
--- a/testsuite/tests/primops/should_run/all.T
+++ b/testsuite/tests/primops/should_run/all.T
@@ -12,3 +12,4 @@ test('T10678',
       only_ways('normal')
      ],
      compile_and_run, ['-O'])
+test('T11296', normal, compile_and_run, [''])



More information about the ghc-commits mailing list