[GHC] #9768: reify returns only first instance of class

#9768: reify returns only first instance of class -------------------------------------+------------------------------------- Reporter: qnikst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | https://gist.github.com/qnikst/b93e7154e78bcc159be2 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- In ghc-7.8 reify returns only first data type that have an instance, here is a code: Test.hs {{{ {-# LANGUAGE TemplateHaskell #-} module Test where import Language.Haskell.TH class C a inner :: ExpQ inner = do ClassI _ instances <- reify ''C let sh = show instances [| sh |] def :: String -> DecsQ def x = let dn = mkName x in do dt <- dataD (cxt []) dn [] [] [] i <- instanceD (cxt []) (appT (conT ''C) (conT dn)) [] -- [d| instance C $(cn) |] return [dt,i] test :: ExpQ test = [| print $inner |] }}} test.hs {{{ {-# LANGUAGE TemplateHaskell #-} import Test def "A" def "B" main = $(test) }}} running test returns: "[InstanceD [] (AppT (ConT Test.C) (ConT Main.A)) []]" under 7.6 test returns: "[InstanceD [] (AppT (ConT Test.C) (ContT Main.B) [], InstanceD [] (AppT (ConT Test.C) (ConT Main.A) []]" -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9768 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9768: reify returns only first instance of class -------------------------------------+------------------------------------- Reporter: qnikst | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | https://gist.github.com/qnikst/b93e7154e78bcc159be2| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire Comment: If you change your `test.hs` to {{{ {-# LANGUAGE TemplateHaskell #-} import Test def "A" def "B" $(return []) main = $(test) }}} it works. The extra splice changes the order of processing of top-level blocks. GHC breaks a module into a sequence of mutually-recursive blocks, separated by top-level declaration splices. But, it seems that the processing of these blocks does not proceed in strict top-to-bottom order. This doesn't quite go against spec -- TH claims to process splices in a non-deterministic order -- but I think we can do better for top-level declaration splices. I'll take a look at this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9768#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9768: Declarations processed in unexpected order in the presence of TH declaration splices -------------------------------------+------------------------------------- Reporter: qnikst | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.3 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | https://gist.github.com/qnikst/b93e7154e78bcc159be2| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by goldfire): * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9768#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9768: Declarations processed in unexpected order in the presence of TH declaration splices -------------------------------------+------------------------------------- Reporter: qnikst | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.3 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | https://gist.github.com/qnikst/b93e7154e78bcc159be2| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * cc: facundo.dominguez (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9768#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9768: Declarations processed in unexpected order in the presence of TH declaration splices -------------------------------------+------------------------------------- Reporter: qnikst | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Template | Version: 7.8.3 Haskell | Keywords: Resolution: wontfix | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | https://gist.github.com/qnikst/b93e7154e78bcc159be2| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => wontfix Comment: GHC's current behavior is actually exactly as advertised (although perhaps unintuitive). From section 7.16.1 of the manual: A declaration group is the group of declarations created by a top- level declaration splice, plus those following it, down to but not including the next top-level declaration splice. The first declaration group in a module includes all top-level definitions down to but not including the first top-level declaration splice. Thus, in the OP's code, `def "B"` and `main` are in the same group, and accordingly, a splice within that group can't reify the group's own types. This could be changed easily enough, but I think a change would make TH strictly less expressive. Using the current behavior, a splice could include part of a declaration (say, just a type signature) and the rest of the declaration can be hand-written outside the splice. If we made a top- level splice its own inviolable group, such a split declaration would be impossible to write. So, I'm closing this ticket, as everything seems OK to me. Do reopen if this is really ruining your day. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9768#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9768: Declarations processed in unexpected order in the presence of TH declaration splices -------------------------------------+------------------------------------- Reporter: qnikst | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Template | Version: 7.8.3 Haskell | Keywords: Resolution: wontfix | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | https://gist.github.com/qnikst/b93e7154e78bcc159be2| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by qnikst): Fair enough. Anyway workaround with adding a `$(return [])` will work for me. Thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9768#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC