Skip to content
Snippets Groups Projects
Commit a7a960e4 authored by takano-akio's avatar takano-akio Committed by Ben Gamari
Browse files

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
parent 05b497ec
No related merge requests found
{-# 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
......
......@@ -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:
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment