[GHC] #14290: Strictness bug with existential contexts on data constructors

GHC ghc-devs at haskell.org
Wed Sep 27 15:16:39 UTC 2017


#14290: Strictness bug with existential contexts on data constructors
-------------------------------------+-------------------------------------
           Reporter:  simonmar       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  highest        |         Milestone:  8.2.2
          Component:  Compiler       |           Version:  8.2.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Incorrect result
  Unknown/Multiple                   |  at runtime
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following:

 {{{
 {-# 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
   }
 }}}

 Fails with `error "xxx"`, when it should succeed. The problem is that the
 strictness signature for the data con wrapper doesn't take into account
 the dictionary fields.

 I have a patch which I'll upload to Phabricator shortly...

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14290>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list