[Git][ghc/ghc][master] 2 commits: testsuite: Fix and extend closure_size test
Marge Bot
gitlab at gitlab.haskell.org
Tue Jun 11 03:53:31 UTC 2019
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
2f945086 by Ben Gamari at 2019-06-11T03:53:25Z
testsuite: Fix and extend closure_size test
This was previously broken in several ways. This is fixed and it also
now tests arrays. Unfortunately I was unable to find a way to continue
testing PAP and FUN sizes; these simply depend too much upon the
behavior of the simplifier.
I also tried to extend this to test non-empty arrays as well but
unfortunately this was non-trivial as the array card size constant isn't
readily available from haskell.
Fixes #16531.
- - - - -
e5d275f4 by Ben Gamari at 2019-06-11T03:53:25Z
ghc-heap: Add closure_size_noopt test
This adds a new test, only run in the `normal` way, to verify the size
of FUNs and PAPs.
- - - - -
4 changed files:
- + libraries/ghc-heap/tests/ClosureSizeUtils.hs
- libraries/ghc-heap/tests/all.T
- libraries/ghc-heap/tests/closure_size.hs
- + libraries/ghc-heap/tests/closure_size_noopt.hs
Changes:
=====================================
libraries/ghc-heap/tests/ClosureSizeUtils.hs
=====================================
@@ -0,0 +1,52 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+-- | Utilities for the @closure_size@ tests
+module ClosureSizeUtils (assertSize, assertSizeUnlifted) where
+
+import Control.Monad
+import GHC.Exts
+import GHC.Exts.Heap.Closures
+import GHC.Stack
+import Type.Reflection
+
+profHeaderSize :: Int
+#if PROFILING
+profHeaderSize = 2
+#else
+profHeaderSize = 0
+#endif
+
+assertSize
+ :: forall a. (HasCallStack, Typeable a)
+ => a -- ^ closure
+ -> Int -- ^ expected size in words
+ -> IO ()
+assertSize x =
+ assertSizeBox (asBox x) (typeRep @a)
+
+assertSizeUnlifted
+ :: forall (a :: TYPE 'UnliftedRep). (HasCallStack, Typeable a)
+ => a -- ^ closure
+ -> Int -- ^ expected size in words
+ -> IO ()
+assertSizeUnlifted x =
+ assertSizeBox (Box (unsafeCoerce# x)) (typeRep @a)
+
+assertSizeBox
+ :: forall a. (HasCallStack)
+ => Box -- ^ closure
+ -> TypeRep a
+ -> Int -- ^ expected size in words
+ -> IO ()
+assertSizeBox x ty expected = do
+ let !size = closureSize x
+ when (size /= expected') $ do
+ putStrLn $ "closureSize ("++show ty++") == "++show size++", expected "++show expected'
+ putStrLn $ prettyCallStack callStack
+ where expected' = expected + profHeaderSize
+{-# NOINLINE assertSize #-}
=====================================
libraries/ghc-heap/tests/all.T
=====================================
@@ -1,11 +1,26 @@
test('heap_all',
- [when(have_profiling(),
- extra_ways(['prof'])),
+ [when(have_profiling(), extra_ways(['prof'])),
# These ways produce slightly different heap representations.
# Currently we don't test them.
omit_ways(['ghci', 'hpc'])
],
compile_and_run, [''])
+
+# Test everything except FUNs and PAPs in all ways.
test('closure_size',
- omit_ways(['ghci', 'hpc', 'prof']),
+ [extra_files(['ClosureSizeUtils.hs']),
+ when(have_profiling(), extra_ways(['prof'])),
+ # These ways produce slightly different heap representations.
+ # Currently we don't test them.
+ omit_ways(['hpc'])
+ ],
+ compile_and_run, [''])
+
+# Test PAPs and FUNs only in normal way (e.g. with -O0)
+# since otherwise the simplifier interferes.
+test('closure_size_noopt',
+ [extra_files(['ClosureSizeUtils.hs']),
+ only_ways(['normal'])
+ ],
compile_and_run, [''])
+
=====================================
libraries/ghc-heap/tests/closure_size.hs
=====================================
@@ -1,25 +1,20 @@
-{-# LANGUAGE BangPatterns #-}
-{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE TypeInType #-}
{-# LANGUAGE ScopedTypeVariables #-}
-import Control.Monad
-import Type.Reflection
-import GHC.Stack
+import GHC.Exts
+import GHC.IO
+import ClosureSizeUtils
-import GHC.Exts.Heap.Closures
+data A = A (Array# Int)
+data MA = MA (MutableArray# RealWorld Int)
+data BA = BA ByteArray#
+data MBA = MBA (MutableByteArray# RealWorld)
+data B = B BCO#
+data APC a = APC a
-assertSize :: forall a. (HasCallStack, Typeable a)
- => a -> Int -> IO ()
-assertSize !x expected = do
- let !size = closureSize (asBox x)
- when (size /= expected) $ do
- putStrLn $ "closureSize ("++show (typeRep @a)++") == "++show size++", expected "++show expected
- putStrLn $ prettyCallStack callStack
-{-# NOINLINE assertSize #-}
-
-pap :: Int -> Char -> Int
-pap x _ = x
-{-# NOINLINE pap #-}
main :: IO ()
main = do
@@ -28,7 +23,26 @@ main = do
assertSize (Nothing :: Maybe ()) 2
assertSize ((1,2) :: (Int,Int)) 3
assertSize ((1,2,3) :: (Int,Int,Int)) 4
- assertSize (id :: Int -> Int) 1
- assertSize (fst :: (Int,Int) -> Int) 1
- assertSize (pap 1) 2
+ MA ma <- IO $ \s ->
+ case newArray# 0# 0 s of
+ (# s1, x #) -> (# s1, MA x #)
+
+ A a <- IO $ \s ->
+ case freezeArray# ma 0# 0# s of
+ (# s1, x #) -> (# s1, A x #)
+
+ MBA mba <- IO $ \s ->
+ case newByteArray# 0# s of
+ (# s1, x #) -> (# s1, MBA x #)
+
+ BA ba <- IO $ \s ->
+ case newByteArray# 0# s of
+ (# s1, x #) ->
+ case unsafeFreezeByteArray# x s1 of
+ (# s2, y #) -> (# s2, BA y #)
+
+ assertSizeUnlifted ma 3
+ assertSizeUnlifted a 3
+ assertSizeUnlifted mba 2
+ assertSizeUnlifted ba 2
=====================================
libraries/ghc-heap/tests/closure_size_noopt.hs
=====================================
@@ -0,0 +1,12 @@
+import ClosureSizeUtils
+
+pap :: Int -> Char -> Int
+pap x _ = x
+{-# NOINLINE pap #-}
+
+main :: IO ()
+main = do
+ assertSize (id :: Int -> Int) 1
+ assertSize (fst :: (Int,Int) -> Int) 1
+ assertSize (pap 1) 2
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/58a5d728d0293110d7e80aa1f067721447b20882...e5d275f45677ed89df310754973a15c522dc1003
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/58a5d728d0293110d7e80aa1f067721447b20882...e5d275f45677ed89df310754973a15c522dc1003
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190610/e5ca6acc/attachment-0001.html>
More information about the ghc-commits
mailing list