[GHC] #12559: Don't ignore addTopDecls in addModFinalizer

GHC ghc-devs at haskell.org
Thu Sep 1 14:48:32 UTC 2016


#12559: Don't ignore addTopDecls in addModFinalizer
-------------------------------------+-------------------------------------
           Reporter:                 |             Owner:
  facundo.dominguez                  |  facundo.dominguez
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.0.2
          Component:  Compiler       |           Version:  8.0.1
           Keywords:  template-      |  Operating System:  Unknown/Multiple
  haskell                            |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #11832
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following program fails to compile because `f` is not found.
 {{{
 -- main.hs
 import M

 main = print (f 0)
 }}}

 {{{
 -- M.hs
 {-# LANGUAGE TemplateHaskell #-}
 module M where

 import Language.Haskell.TH.Syntax

 g :: IO ()
 g = $(do addModFinalizer (do d <- [d| f x = (2 :: Int) |]; addTopDecls d)
          [| return ()|]
      )
 }}}

 {{{
 $ runghc main.hs

 main.hs:3:15: Not in scope: ‘f’
 }}}

 This bug is problematic to produce top-level declarations which depend on
 the output of `reify` for local variables, which can only run in
 `addModFinalizer`.

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


More information about the ghc-tickets mailing list