[GHC] #12559: Don't ignore addTopDecls in module finalizers (was: Don't ignore addTopDecls in addModFinalizer)

GHC ghc-devs at haskell.org
Thu Sep 1 16:08:32 UTC 2016


#12559: Don't ignore addTopDecls in module finalizers
-------------------------------------+-------------------------------------
        Reporter:                    |                Owner:
  facundo.dominguez                  |  facundo.dominguez
            Type:  bug               |               Status:  patch
        Priority:  normal            |            Milestone:  8.0.2
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:  template-
                                     |  haskell
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #11832            |  Differential Rev(s):  Phab:D2505
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by facundo.dominguez:

@@ -29,2 +29,2 @@
- the output of `reify` for local variables, which can only run in
- `addModFinalizer`.
+ the output of `reify` for local variables, which can only run in a
+ finalizer.

New description:

 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 a
 finalizer.

--

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


More information about the ghc-tickets mailing list