Skip to content
Snippets Groups Projects
Commit a0671e2d authored by Simon Marlow's avatar Simon Marlow Committed by Ben Gamari
Browse files

mkDataConRep: fix bug in strictness signature (#14290)

The strictness signature for a data con wrapper wasn't including any
dictionary arguments, which meant that bangs on the fields of a
constructor with an existential context would be moved to the wrong
fields.  See T14290 for an example.

Test Plan:
* New test T14290
* validate

Reviewers: simonpj, niteria, austin, bgamari, erikd

Reviewed By: simonpj, bgamari

Subscribers: rwbarton, thomie

GHC Trac Issues: #14290

Differential Revision: https://phabricator.haskell.org/D4040

(cherry picked from commit 5935acdb)
parent 78e67391
No related branches found
No related tags found
No related merge requests found
...@@ -528,7 +528,11 @@ mkDataConRep dflags fam_envs wrap_name mb_bangs data_con ...@@ -528,7 +528,11 @@ mkDataConRep dflags fam_envs wrap_name mb_bangs data_con
wrap_sig = mkClosedStrictSig wrap_arg_dmds (dataConCPR data_con) wrap_sig = mkClosedStrictSig wrap_arg_dmds (dataConCPR data_con)
wrap_arg_dmds = map mk_dmd arg_ibangs wrap_arg_dmds =
replicate (length theta) topDmd ++ map mk_dmd arg_ibangs
-- Don't forget the dictionary arguments when building
-- the strictness signature (#14290).
mk_dmd str | isBanged str = evalDmd mk_dmd str | isBanged str = evalDmd
| otherwise = topDmd | otherwise = topDmd
......
{-# LANGUAGE ExistentialQuantification #-}
module Main (main) where
main :: IO ()
main = r `seq` return ()
r :: Rec
r = Rec{ a = error "xxx", b = 3, c = True }
class C t
instance C Bool
data Rec = forall t. C t => Rec
{ a :: ()
, b :: !Int
, c :: t
}
...@@ -15,3 +15,4 @@ test('T11555a', normal, compile_and_run, ['']) ...@@ -15,3 +15,4 @@ test('T11555a', normal, compile_and_run, [''])
test('T12368', exit_code(1), compile_and_run, ['']) test('T12368', exit_code(1), compile_and_run, [''])
test('T12368a', exit_code(1), compile_and_run, ['']) test('T12368a', exit_code(1), compile_and_run, [''])
test('T13380', [expect_broken(13380), exit_code(1)], compile_and_run, ['']) test('T13380', [expect_broken(13380), exit_code(1)], compile_and_run, [''])
test('T14290', normal, compile_and_run, [''])
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