[Git][ghc/ghc][wip/T26748] Account for "stupid theta" in demand sig for DataCon wrappers
Matthew Craven pushed to branch wip/T26748 at Glasgow Haskell Compiler / GHC Commits: a65d92f2 by Matthew Craven at 2026-01-08T09:43:37-05:00 Account for "stupid theta" in demand sig for DataCon wrappers Fixes #26748. - - - - - 4 changed files: - compiler/GHC/Types/Id/Make.hs - + testsuite/tests/dmdanal/should_run/T26748.hs - + testsuite/tests/dmdanal/should_run/T26748.stdout - testsuite/tests/dmdanal/should_run/all.T Changes: ===================================== compiler/GHC/Types/Id/Make.hs ===================================== @@ -825,9 +825,10 @@ mkDataConRep dc_bang_opts fam_envs wrap_name data_con -- LFInfo stores post-unarisation arity wrap_arg_dmds = - replicate (length theta) topDmd ++ map mk_dmd arg_ibangs + replicate (length stupid_theta + length theta) topDmd + ++ map mk_dmd arg_ibangs -- Don't forget the dictionary arguments when building - -- the strictness signature (#14290). + -- the strictness signature (#14290, #26748). mk_dmd str | isBanged str = evalDmd | otherwise = topDmd ===================================== testsuite/tests/dmdanal/should_run/T26748.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE Haskell98 #-} +module Main (main, x) where + +data Eq a => D a = MkD { lazy_field :: a, strict_field :: !a } + +x :: D () +{-# INLINABLE x #-} +x = MkD { lazy_field = error "urk", strict_field = () } + +main :: IO () +main = print (strict_field x) ===================================== testsuite/tests/dmdanal/should_run/T26748.stdout ===================================== @@ -0,0 +1 @@ +() ===================================== testsuite/tests/dmdanal/should_run/all.T ===================================== @@ -34,3 +34,4 @@ test('T22475b', normal, compile_and_run, ['']) test('T22549', normal, compile_and_run, ['-fdicts-strict -fno-specialise']) test('T23208', exit_code(1), multimod_compile_and_run, ['T23208_Lib', 'T23208']) test('T25439', normal, compile_and_run, ['']) +test('T26748', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a65d92f2c1b64c29473ceb11979a38a2... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a65d92f2c1b64c29473ceb11979a38a2... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Matthew Craven (@clyring)