[commit: ghc] master: Make the test for #11108 less fragile (a7a960e)
git at git.haskell.org
git at git.haskell.org
Mon Sep 5 21:00:00 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/a7a960e43c34e40e1656fa1505605f756a44bb71/ghc
>---------------------------------------------------------------
commit a7a960e43c34e40e1656fa1505605f756a44bb71
Author: Takano Akio <tak at anoak.io>
Date: Mon Sep 5 15:52:37 2016 -0400
Make the test for #11108 less fragile
This change should close #11108 by fixing the test case.
This commit fixes two issues:
* Make sure that each weak pointer we allocate has a constructor as the
key, not a thunk. A failure to do so meant these weak pointers died
prematurely on the 'ghci' WAY.
* Don't print anything in the finalizer, because they are not guaranteed
to run.
Test Plan: validate
Reviewers: austin, simonmar, erikd, bgamari
Reviewed By: erikd, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2512
GHC Trac Issues: #11108
>---------------------------------------------------------------
a7a960e43c34e40e1656fa1505605f756a44bb71
testsuite/tests/rts/T11108.hs | 6 +++---
testsuite/tests/rts/all.T | 2 +-
2 files changed, 4 insertions(+), 4 deletions(-)
diff --git a/testsuite/tests/rts/T11108.hs b/testsuite/tests/rts/T11108.hs
index d70f333..63e70c1 100644
--- a/testsuite/tests/rts/T11108.hs
+++ b/testsuite/tests/rts/T11108.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE RecursiveDo, LambdaCase #-}
+{-# LANGUAGE RecursiveDo, LambdaCase, BangPatterns #-}
import Control.Monad.Fix
import Data.IORef
@@ -22,8 +22,8 @@ makePull f = do
-- This seems to be the culprit, changing the order makes the weakRef get gc'ed
-- In this configuration it crashes
- foo <- Pull weak f <$> newIORef [] <*> newIORef Nothing
- weak <- mkWeakPtr foo (Just $ print "died")
+ !foo <- Pull weak f <$> newIORef [] <*> newIORef Nothing
+ weak <- mkWeakPtr foo Nothing
return foo
diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T
index b82036f..9692846 100644
--- a/testsuite/tests/rts/all.T
+++ b/testsuite/tests/rts/all.T
@@ -267,7 +267,7 @@ test('T9078', only_ways(['threaded1']), compile_and_run, [''])
test('T10017', [ when(opsys('mingw32'), skip)
, only_ways(threaded_ways), extra_run_opts('+RTS -N2 -RTS') ], compile_and_run, [''])
-test('T11108', expect_broken_for(11108, ['ghci', 'hpc']), compile_and_run, [''])
+test('T11108', normal, compile_and_run, [''])
test('rdynamic', [ unless(opsys('linux') or opsys('mingw32'), skip)
# this needs runtime infrastructure to do in ghci:
More information about the ghc-commits
mailing list