[GHC] #12777: reify yields the wrong type in the presence of functional rependencies

GHC ghc-devs at haskell.org
Fri Oct 28 20:30:14 UTC 2016


#12777: reify yields the wrong type in the presence of functional rependencies
-------------------------------------+-------------------------------------
           Reporter:                 |             Owner:
  facundo.dominguez                  |
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.0.2
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{reify}}} yields an incomplete type in the following program.

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE FunctionalDependencies #-}
 module B where
 import Language.Haskell.TH as TH
 import Language.Haskell.TH.Syntax as TH

 class C a b | a -> b where
   yo :: a -> IO b

 instance C Bool Int where
   yo = undefined

 t3 :: IO ()
 t3 = do
   x <- yo True
   $(do addModFinalizer $ TH.reify 'x >>= runIO . print
        [| return () |]
    )
 }}}

 {{{
 $ inplace/bin/ghc-stage2 B.hs -fforce-recomp
 [1 of 1] Compiling B                ( B.hs, B.o )
 VarI x_1627401898 (VarT a_1627404604) Nothing
 }}}

 The problem seems to be that finalizers run before functional dependencies
 are considered.

 Hacking ghc to run finalizers after {{{simplifyTop}}} produces the
 expected output instead:
 {{{
 $ inplace/bin/ghc-stage2 B.hs -fforce-recomp
 [1 of 1] Compiling B                ( B.hs, B.o )
 VarI x_1627404863 (ConT GHC.Types.Int) Nothing
 }}}

 Would anyone object to running finalizers after {{{simplifyTop}}}? This
 implies that finalizers shouldn't add definitions (with {{{addTopDecls}}})
 which depend on {{{simplifyTop}}} to be type-checked.

 Another option is to call {{{simplifyTop}}} before and after running
 finalizers. But is it safe to do so?

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


More information about the ghc-tickets mailing list