[GHC] #9813: Error when reifying type constructor

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | 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: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- The following code works under ghc-7.6.3 and template-haskell-2.8.0.0: {{{#!hs {-# LANGUAGE TemplateHaskell #-} data Huh = ThisDefinitely | UsedToWork constructorNames :: String constructorNames = $(do ty <- reify ''Huh let showCon (NormalC n _) = nameBase n strs = case ty of (TyConI (DataD _ _ _ cons _)) -> map showCon cons return . LitE . StringL $ concat strs) main = putStrLn constructorNames }}} Printing the following at compile time: {{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.4.0.1 ... linking ... done. Loading package deepseq-1.3.0.1 ... linking ... done. Loading package containers-0.5.0.0 ... linking ... done. Loading package pretty-1.1.1.0 ... linking ... done. Loading package template-haskell ... linking ... done. Linking Main ... }}} and then successfully executing: {{{ $ ./Main ThisDefinitelyUsedToWork }}} However, using ghc 7.8.3/template-haskell-2.9.0.0 I get the following compile error: {{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package containers-0.5.5.1 ... linking ... done. Loading package pretty-1.1.1.1 ... linking ... done. Loading package template-haskell ... linking ... done. Main.hs:8:22: ‘Huh’ is not in the type environment at a reify In the splice: $(do { ty <- reify ''Huh; let showCon (NormalC n _) = ... ....; return . LitE . StringL $ concat strs }) }}} Is this expected? I couldn't see anything in the GHC release notes to suggest this should no longer work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Description changed by owst: Old description:
The following code works under ghc-7.6.3 and template-haskell-2.8.0.0:
{{{#!hs {-# LANGUAGE TemplateHaskell #-}
data Huh = ThisDefinitely | UsedToWork
constructorNames :: String constructorNames = $(do ty <- reify ''Huh let showCon (NormalC n _) = nameBase n strs = case ty of (TyConI (DataD _ _ _ cons _)) -> map showCon cons return . LitE . StringL $ concat strs)
main = putStrLn constructorNames }}}
Printing the following at compile time:
{{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.4.0.1 ... linking ... done. Loading package deepseq-1.3.0.1 ... linking ... done. Loading package containers-0.5.0.0 ... linking ... done. Loading package pretty-1.1.1.0 ... linking ... done. Loading package template-haskell ... linking ... done. Linking Main ... }}}
and then successfully executing:
{{{ $ ./Main ThisDefinitelyUsedToWork }}}
However, using ghc 7.8.3/template-haskell-2.9.0.0 I get the following compile error: {{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package containers-0.5.5.1 ... linking ... done. Loading package pretty-1.1.1.1 ... linking ... done. Loading package template-haskell ... linking ... done.
Main.hs:8:22: ‘Huh’ is not in the type environment at a reify In the splice: $(do { ty <- reify ''Huh; let showCon (NormalC n _) = ... ....; return . LitE . StringL $ concat strs }) }}}
Is this expected? I couldn't see anything in the GHC release notes to suggest this should no longer work.
New description: The following code works under ghc-7.6.3 and template-haskell-2.8.0.0: {{{#!hs {-# LANGUAGE TemplateHaskell #-} data Huh = ThisDefinitely | UsedToWork constructorNames :: String constructorNames = $(do ty <- reify ''Huh let strs = case ty of (TyConI (DataD _ _ _ cons _)) -> map showCon cons showCon (NormalC n _) = nameBase n return . LitE . StringL $ concat strs) main = putStrLn constructorNames }}} Printing the following at compile time: {{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.4.0.1 ... linking ... done. Loading package deepseq-1.3.0.1 ... linking ... done. Loading package containers-0.5.0.0 ... linking ... done. Loading package pretty-1.1.1.0 ... linking ... done. Loading package template-haskell ... linking ... done. Linking Main ... }}} and then successfully executing: {{{ $ ./Main ThisDefinitelyUsedToWork }}} However, using ghc 7.8.3/template-haskell-2.9.0.0 I get the following compile error: {{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package containers-0.5.5.1 ... linking ... done. Loading package pretty-1.1.1.1 ... linking ... done. Loading package template-haskell ... linking ... done. Main.hs:8:22: ‘Huh’ is not in the type environment at a reify In the splice: $(do { ty <- reify ''Huh; let showCon (NormalC n _) = ... ....; return . LitE . StringL $ concat strs }) }}} Is this expected? I couldn't see anything in the GHC release notes to suggest this should no longer work. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): Template Haskell made no guarantees about the ordering of splice execution in 7.6.3, or of what definitions were available to `reify`. 7.8.3, on the other hand, says this (user manual, end of section 7.16.1):
The type environment seen by reify includes all the top-level declaration up to the end of the immediately preceding declaration group, but no more.
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.
So, I'd say that you were lucky that it worked in 7.6.3, but this is not erroneous behavior in 7.8.3. You can also fix the problem, by introducing a top-level splice, say {{{ $( return [] ) }}} After the declaration of `Huh`. Please close the ticket if you agree with my analysis. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by owst): Hmm, I'm not particularly convinced. This extract: "The first declaration group in a module includes all top-level definitions down to but not including the first top-level declaration splice." seems to suggest that the declaration of Huh *is* included in the first declaration group, which is the immediately preceding declaration group to the splice. Am I misunderstanding something? The proposed "fix" seems somewhat spurious to me. Do you not agree that the original program seems reasonable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): Only top-level declaration splices break up declaration groups. Your code has an expression splice, which is in the first declaration group and thus can't "see" it. I agree that your code ''is'' reasonable, but I also think that 7.8's behavior of breaking things into declaration groups is more predictable (once you know the rule). In general, otherwise, it would be quite hard for a human to figure out exactly which things are reifiable from a given splice -- it would all depend on GHC's internal topological sorting process. If you can propose an alternative, straightforward rule defining what should be available to `reify`, I'd be interested. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by owst): D'oh yes! I misread/misunderstood. Perhaps the manual could be tweaked to make the difference clear. Without understanding the implications, couldn't encountering an expression splice force the end of the current declaration group? In other words, act as if the splice was a declaration splice; since we can't have non-top-level type declarations, I think this might work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): You are an ideal person to suggest a concrete wording change to the manual since you know what you misunderstood. Would you care to do that? No, a declaration splice can't force the end of a declaration group. What if it was mutually recursive with declarations further down? What if the mutually recursive group was scattered over the file? This way lies madness. That said, I am a bit surprised. The error message says that the renamer- lookup of `Huh` is failing, but I'd expect it to have brought all the names in the current group into scope. Moreover, types declarations are (reliably) typechecked before values decls. Worth looking into. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by owst): Yes, I agree I am, I will try to suggest some edits. And yes, I had a feeling mutually-recursive bindings would be the source of pain! Hmm. My next thought is why not just create declaration "groups" for each top-level declaration? What are we gaining by requiring groups with >1 member? If this happened, the definition of {{{Huh}}} would be its own declaration group, which would precede the reify, and all would be good... or would it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: 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: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: ryan.gl.scott@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Template Haskell Comment: Replying to [comment:7 owst]:
Yes, I agree I am, I will try to suggest some edits.
Feel free to just post them here in a comment. Someone else can polish it and put it in the user's guide. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Changes (by owst): * differential: => Phab:D1899 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor
-------------------------------------+-------------------------------------
Reporter: owst | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 7.8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1899
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Apologies that it took me so long from saying I'll make the user guide changes to actually making them; thanks for the nudge thomie! Having made the doc changes, I'm still not satisfied about the {{{$(return [])}}} solution and I'd definitely like to try to attempt to make the "reasonable" use case work. To be clear, consider: {{{ data A = A f :: Int -> Int f x = x + 1 data B = B C g1 :: Int -> Int g1 x = 1 + g2 x exprContainingSplice1 = $(...) data C = C g2 :: Int -> Int g2 x = x + 2 exprContainingSplice2 = $(...) }}} Naively, I'd expect the splice in {{{ exprContainingSplice1 }}} to be able to refer to {{{A}}} and {{{f}}}, but ''not'' {{{B}}} or {{{g1}}}, since they are in some sense "not fully defined" at the point the splice is encountered (assuming a top-to-bottom processing, rather than some topological-sorted graph-traversal). I'd also expect the splice in {{{ exprContainingSplice2 }}} to be able to able to refer to all functions and and data types except probably(?) {{{exprContainingSplice1}}} and {{{exprContainingSplice2}}}. Can this be made to work, or is it nonsense? Simon's earlier comment
Moreover, types declarations are (reliably) typechecked before values decls. Worth looking into. intrigues me - I think he suggests that it might be possible for a splice in {{{ exprContainingSplice1 }}} to refer to {{{A}}}, but not {{{f}}}?
If it is likely to be at all possible, does anyone have any pointers of likely starting points/functions I should definitely explore etc. I'd like to get my hands dirty! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): There's two separate questions at work here: 1. Is there a rule that humans can understand and apply easily telling these humans what is available for reification at a certain splice? 2. Is the rule proposed in (1) implementable? I'm worried about tackling (2) before nailing (1). It sounds like you're suggesting a rule such as this: A. All declarations appearing above a splice such that all dependencies of the declaration are also above the splice are available. I don't love this rule, because it takes declaration order into account in a non-trivial way. Haskellers tend not to worry about top-to-bottom ordering. (Of course, we already violate this convention with top-level splices.) But maybe others like this rule and think it's easy enough. But then what about B. All declarations that do not depend on any splice are in scope for all splices. This is a different rule than the first. Is it easier to understand? According to Simon's suggestion, we might consider C. All types (as broken up by top-level splices) are available for all splices, but functions are available only according to the top-to-bottom rule around top-level splices. I think any of these rules might be implementable. But what's best? Let's settle on a design that can be simply stated and understood before worrying about implementation. Another way of saying this: let's get our brains dirty before we get our hands dirty. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Excellent points goldfire. My thoughts on your three suggestions: * A) As you say, declaration order isn't something we normally have to consider in Haskell, which is a drawback I hadn't thought about, * C) Sounds simple, but seems a little arbitrary that types would be available to all splices, but functions only according to the top-to- bottom ordering, why should types be more important than terms? :-) * B) Certainly sounds simple and using it in my example above, {{{exprContainingSplice1}}} and {{{exprContainingSplice1}}} would have access to all of {{{A}}},{{{B}}},{{{f}}},{{{g1}}} and {{{g2}}} but ''not'' each other, which seems very reasonable. A question/thought: should {{{reify}}} be able to determine information about datatypes/expressions, but have them still be unavailable for compile-time evaluation? E.g. consider the following: {{{#!hs import Language.Haskell.TH double :: (Num a) => a -> a double x = x * 2 data D = D Int deriving Show doReify = do print $(reify 'double >>= litE . stringL . show) print $(reify 'D >>= litE . stringL . show) doEval = do print $(litE . integerL $ double 10) print $(litE . stringL . show $ D 10) main = doReify >> doEval }}} under the B) suggestion, the following will fail to compile (with a stage restriction error) unless the definition and usage of {{{doEval}}} are commented out. Is that surprising? Is there a technical reason to rule out {{{doEval}}}? The user guide currently has this to say
You can only run a function at compile time if it is imported from another module. That is, you can't define a function in a module, and call it from within a splice in the same module. (It would make sense to do so, but it's hard to implement.) is this related to why {{{reify myFunction}}} doesn't contain the source of {{{myFunction}}} - as per #1831?
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): If we are willing to expose GHC's internal toposort of declarations (that is, its process of finding mutually recursive groups, without regard to top-to-bottom ordering, and then processing these groups in dependency order), then we might be able to do away with the stage restriction. Indeed, I was surprised to see that the Haskell 2010 report even contains a description of the toposort: see [https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-880004.... Section 4.5.1]. The context there is different than here, but it all still relies on finding chunks of perhaps-mutually-recursive definitions. So perhaps the process is this: 1. Split up the module into regions separated by top-level declaration splices. 2. Within each region, chunk the declarations into mutually recursive groups. Any declaration with a splice in it is considered to depend on all other declarations in the region. 3. Process the chunks in dependency order, making already-processed chunks available both for a. reification b. calling in a splice (i.e. loosening the stage restriction) I actually that's not quite so bad. It's not really too hard to understand. It might be some work to implement; it will depend on the details. But it surely seems ''possible'' to implement. And, as far as I can see, this is a loosening of existing restrictions. No code that is accepted today would be rejected by these rules. What do you think? And, in answer to your question, I don't think this is much related to #1831. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): I think it's reasonable to expose the toposort of declarations - users are presumably used to declarations not being processed top-to-bottom already; it seems more consistent to expose toposorted-ness here too, rather than use a different rule. Some thoughts about your proposal (which I like the gist of!): * W.r.t. step 1. I'd quite like the splice in {{{f}}}: {{{#!hs f x = x ++ $(reify 'g ...) $(return []) g x = x + 1 }}} to be able to refer to {{{g}}}. It is in a different declaration group, but I think that it should be visible. However, I can't see an easy way around the need for declaration groups, so maybe it's not possible. * In step 2. I think it would be necessary that a splice within a declaration cannot refer to the declaration itself (though I'm not ''sure'' this is a problem?)
No code that is accepted today would be rejected by these rules. This seems particularly desirable to me!
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:16 owst]:
* In step 2. I think it would be necessary that a splice within a declaration cannot refer to the declaration itself (though I'm not ''sure'' this is a problem?)
Right. We at least can't allow an expression splice to refer to the type of the containing declaration: {{{ x = $(if the type of x is Char then [| False |] else [| 'a' |]) }}} So the topological sorting in goldfire's steps 2-3 is a bit overkill, and what is really going on is: 2-3. Within each region, process all the declarations that do not contain splices first. Then process all the declarations that do contain splices, making the declarations in the former group available for reification and calling. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:17 rwbarton]:
Right. We at least can't allow an expression splice to refer to the type of the containing declaration: {{{ x = $(if the type of x is Char then [| False |] else [| 'a' |]) }}}
Nice example!
2-3. Within each region, process all the declarations that do not
contain splices first. Then process all the declarations that do contain splices, making the declarations in the former group available for reification and calling. Hmm, I think the topological sorting ''is'' required within regions, what about: {{{#!hs module Foo where f = $(...) g = $(reify 'f ...) h = 1 }}} I think we want to, in order: 1. Process {{{h}}} 2. Process {{{f}}}, which can refer to {{{h}}} but not {{{f}}} or {{{g}}} 3. Process {{{g}}}, which can ref to {{{h}}} and {{{f}}}, but ''not'' {{{g}}}. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I think this is too optimistic. In general we can't analyze the argument of `reify` in `g` to know that it refers only to `f`. Plus the `...` could contain arbitrary code that could use functions in other packages that reify arbitrary names. I would say that both `f` and `g` can only refer to `h`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:19 rwbarton]:
I think this is too optimistic. In general we can't analyze the argument of `reify` in `g` to know that it refers only to `f`. Plus the `...` could contain arbitrary code that could use functions in other packages that reify arbitrary names.
Oh of course, yes. I was only thinking about `reify 'name`, rather than passing an arbitrary `Name` to `reify`.
I would say that both `f` and `g` can only refer to `h`.
I agree. I think we must rule out dependencies on expressions that contain splices. e.g. in the following: {{{#!hs f x = $(...) g y = f ... }}} `g` does not contain a splice, but depends on `f`, which does. Therefore, if this is to be allowed, we must process `f` before `g`. I think it could be done, but that way probably lies madness. Taking goldfire and rwbarton's suggestions into account, I think the procedure would be: 1. Split the module into declaration groups and process top-to-bottom, 2. For each declaration group, partition the declarations within to those that contain splices (S), and those that do not (NS), 3. Process NS first, then S. Splices within S can refer (either in `reify` or via evaluation) to all names declared in NS, but no names within S. This allows: {{{#!hs f = () data C = C g = $(reify 'f >> reify 'C >> reify ''C >> ...) $(return []) h = $(reify 'f >> reify 'C >> reify ''C >> reify 'g >> ...) }}} but not: {{{#!hs f = () g = $(reify 'f ...) -- ok h = $(reify 'g ...) -- f not in type environment in reify i = ... g ... h ... -- Not in scope g or h j = k $(reify 'k ...) -- Not in scope k (and k not in type environment in reify) $(return []) k x = ... }}} Does that seem reasonable, and likely to be implementable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Recent arguments have not shifted me from my proposal in comment:15. What about {{{ f = g 5 g = $(...) }}} The suggestion to process declarations that do not contain a splice before declarations that do fails here. Instead, we recognize that `f` and `g` are in a mutually recursive group and process them together. `g` cannot reify `f`. Note that comment:15 says that only already-processed declarations (that is, not in the same mutually recursive group) are available. It does strike me (inspired by comment:16) that with all this toposorting going on, we may be able to avoid having top-level splices break the file up into declaration groups. The current behavior seems something like a feeble attempt at a toposort, anyway. I suppose changing this would break {{{ f = $(...) $( ... reify 'f ... ) }}} though. (That code would work now.) So, upon further thought, this particular aspect of the change seems dead in the water. Note that my pessimism here is only about comment:16, not comment:15. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:21 goldfire]:
{{{ f = g 5 g = $(...) }}}
The suggestion to process declarations that do not contain a splice before declarations that do fails here.
Instead, we recognize that `f` and `g` are in a mutually recursive group and process them together. `g` cannot reify `f`. Note that comment:15 says
Yes, indeed, it is very similar to my example at the top of comment:20, but I felt it wouldn't be easy to handle. Perhaps it is... that only already-processed declarations (that is, not in the same mutually recursive group) are available. Are `f` and `g` mutually recursive? Since you explicitly say `g` ''cannot'' reify `f` - does `f` therefore just depend on `g`? What about in: {{{ f = e $(...) c = $(...) e = c ... d = $(...) a = ... b ... b = ... a ... }}} I think an processing order: `(a b) < (c d) < e < f` could work: 1. `a, b` are in scope to reify/call for `c`, 1. `c` is ''not'' in scope to reify/call for `d` (we cannot in general determine what `d` `reify`s so cannot order the splices - as per comment:19) 1. `a, b, c, d` are in scope to reify/call in `e`, there is a data dependency between `e` and `c` (and thus implicitly `d`): `e` is ordered ''after'' `c` 1. `a, b, c, d, e` are in scope to reify/call in `f` since there is a data dependency between `f` and `e`: `f` is ordered ''after'' `e`.
It does strike me (inspired by comment:16) that with all this toposorting going on, we may be able to avoid having top-level splices break the file up into declaration groups. The current behavior seems something like a feeble attempt at a toposort, anyway.
Indeed, I think that would be nice for a consistent story. However, how do you order top-level declarations in the toposort? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:22 owst]:
Are `f` and `g` mutually recursive? Since you explicitly say `g` ''cannot'' reify `f` - does `f` therefore just depend on `g`?
We declare that they are. That's what's meant by "anything with a splice depends on anything else". It's true that the splice can't do much reify `f`, but it can certainly produce code which calls `f`.
What about in: {{{ f = e $(...) c = $(...) e = c ... d = $(...) a = ... b ... b = ... a ... }}}
I think an processing order: `(a b) < (c d) < e < f` could work:
I don't think this would quite work. What if `c` calls `f`? That is, `c = $(varE (mkName (['a'..] !! 5 : [])))`. We don't know without running the splice, so we say that anything with a splice depends on anything else in the region.
It does strike me (inspired by comment:16) that with all this
toposorting going on, we may be able to avoid having top-level splices break the file up into declaration groups. The current behavior seems something like a feeble attempt at a toposort, anyway.
Indeed, I think that would be nice for a consistent story. However, how
do you order top-level declarations in the toposort? Perhaps I was confusing. Sorry. I changed my mind as I wrote my response -- in the end, I don't think this would work, because it would assume that expression splices above the top-level splice could depend on declarations below the top-level splice, which might break existing code (and with no workaround). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): In comment:19 I neglected the case of comment:20, in which a function without a splice refers to a function with a splice. I still think the main point, that there are only two kinds of declaration per declaration group is correct. In each declaration group we have * the declarations which do not use a splice, either directly or via reference to another declaration in the same group which uses a splice; * the declarations which do use a splice, either directly or via reference.... We process the first group, then process the second group, making the first group (but none of the second group) available to reify. This is just supposed to be a restatement of goldfire's comment:15, taking into account that "any declaration with a splice in it is considered to depend on all other declarations in the region" means that there are effectively at most two of goldfire's "chunks" per declaration group. (In fact, there might be several mutually recursive groups of declarations that do not (even indirectly) contain splices. But then it doesn't matter whether we process them as a single group or as several groups, because the declarations in the group contain no splices anyways.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Ah. Understood re comment:24. I was thinking more in terms of GHC's implementation, which does all the chunking already. But you're right that we can explain this to users in terms of just two chunks, the non-splicy one and then the splicy one, with the caveat that spliciness is infectious. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Thank you both for clarifying things. So, to be explicit, the proposal is (at a conceptual level) now: 1. Split the module into declaration groups (DG) and process top-to- bottom, 2. For each DG: a. partition the declarations within it to two sets: those that contain splices (directly or via reference), which we refer to as S, and those that do not, which we refer to as NS, b. Process NS first, then S. Splices within S can refer (either with `reify` or via evaluation) to all names declared in NS or previous DGs), but no names within S. This allows: {{{ f = $(mapM reify ['C, ''C, 'i] >>= ...) -- all names are in NS g = h f h x = $(LitE . StringL . i . show <$> reify 'i) -- both call and reify i i x = x data C = C $(return []) -- In a later DG, all earlier names are available, as are those in NS j = $(mapM reify ['C, ''C, 'f, 'g, 'h, 'i, 'k] >>= ...) k = () }}} Here, we have two declaration groups: 1. NS = `{i, C}`, S = `{f, g, h}` 2. NS = `{k}`, S = `{j}` (with `i, C, f, g, h` all available for `reify`/evaluation) but not: {{{ f = () g = $(reify 'f ...) -- ok h = ... g ... i = $(reify 'g ...) -- Error: f is in S in this declaration group j = $(reify 'h ...) -- Error: h is in S in this declaration group k = $(reify 'l ...) -- Error: l is declared in the next declaration group $(return []) l x = ... }}} Here we also have two declaration groups, and in particular, `h` is contained in ''S'' in the first declaration group. So vs today: 1. We loosen the stage restriction (allowing e.g. `h` to call `i`) 2. Allow "no-splice" expressions to be referred to from a splice within the same declaration group (allowing e.g. `f` to `reify` both `C` and `i`). Both whilst not breaking existing programs. This seems good! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): This all sounds great except for one thing. Do we have a plan for actually loosening the stage restriction? The stage restriction exists for technical reasons, not conceptual reasons. The stage restriction currently applies to the module as a whole. It says you cannot use an identifier that was defined in a module within a splice in the same module. Clearly if the use is in a later declaration group than the definition, there is no problem in principle with lifting the restriction. But in order to do so, we would have to run the declaration group containing the definition through the entire compiler pipeline, right up to linking, so that we can load it to run the splice in the latter declaration group to begin type checking it. GHC just isn't organized to work that way currently. The user's guide has this to say on the subject:
You can only run a function at compile time if it is imported from another module. That is, you can't define a function in a module, and call it from within a splice in the same module. (It would make sense to do so, but it's hard to implement.)
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

This all sounds great except for one thing. Do we have a plan for actually loosening the stage restriction? The stage restriction exists for technical reasons, not conceptual reasons.
The stage restriction currently applies to the module as a whole. It says you cannot use an identifier that was defined in a module within a splice in the same module. Clearly if the use is in a later declaration group than the definition, there is no problem in principle with lifting
#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:27 rwbarton]: the restriction. But in order to do so, we would have to run the declaration group containing the definition through the entire compiler pipeline, right up to linking, so that we can load it to run the splice in the latter declaration group to begin type checking it. GHC just isn't organized to work that way currently. An incredibly good point. To answer the first question simply: I don't, no. I haven't hacked on GHC before, so was attempting to flesh out my original bug report to find a change that I might get my teeth into. I have to admit I hadn't thought about the technical barriers and thus rather haphazardly threw about the "let's loosen the stage restriction" part!
The user's guide has this to say on the subject: ...
Indeed - I pasted that very snippet in comment:14, but I hadn't appreciated what the technical barriers were. What do you think is a sensible step forward? Change 2.b. in my previous comment to "Process NS first, then S. Splices within S can refer (via reify but ''not'' evaluation) to all names declared in NS or previous DGs), but no names within S"? That way, my original program in this ticket would work, but I wouldn't need any of the complexity of changing the stage restriction too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Yes, I think that is practical in the short term. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I'm fully agreed with the last volley of posts and have nothing new to contribute. @owst, it sounds like you want a go at implementing this ("this" being without the stage-restriction stuff). Go right ahead! :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
But in order to do so, we would have to run the declaration group containing the definition through the entire compiler pipeline, right up to linking, so that we can load it to run the splice in the latter declaration group to begin type checking it. GHC just isn't organized to work that way currently.
Yes, this is the main reason for the fairly draconian staging restriction at present. But that's only when you want to RUN a splice. If you merely want to reify a type declared "earlier" (as in the Description of this ticket), that's much less stressful. But it exists already {{{ data F = MkF $(makeLenses 'F) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:31 simonpj]:
Yes, this is the main reason for the fairly draconian staging restriction at present. But that's only when you want to RUN a splice. If you merely want to reify a type declared "earlier" (as in the Description of this ticket), that's much less stressful. But it exists already {{{ data F = MkF $(makeLenses 'F) }}}
Absolutely, since `F` is defined in the ''previous'' declaration group to `makeLenses 'F`. My proposal is to allow: {{{ data F = MkF f x = x g = $(mapM reify [''F, 'MkF, 'f] ...) }}} to work too (i.e. allow access via `reify` to (certain) declarations in the ''same'' declaration group). Implementation-wise, I can imagine that the changes will be something along the lines of: 1. Partition the expressions in a declaration group into those that contain splices, and those that do not, 1. Make each expression that contains a splice implicitly depend on all expressions that do not contain splices, 1. Traverse the the toposorted dependency graph and mark all nodes below or containing a splice as "splicy", 1. Process all nodes that are not marked splicy, 1. Make available the information about the non-splicy nodes in the environment, 1. Process all splicy nodes. Presumably, much of this can be taken from the code used to implement the features pointed out by Simon. I will likely start taking a serious look at this tonight. Any pointers/suggestions gratefully received! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
My proposal is to allow: ....
That does look feasible, since the code you are running in the splice all comes from other modules. Do you have a compelling use-case? Most of the debate here is about mechanism. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:33 simonpj]:
That does look feasible, since the code you are running in the splice all comes from other modules.
Do you have a compelling use-case? Most of the debate here is about mechanism.
My original report was modified from a program (https://github.com/owst/Penrose/blob/master/Main.hs#L139) where I do some rudimentary commandline option parsing using a deriving Read instance. To generate the usage of the program, I map over my Option type's constructors and show each one. Something along the lines of: {{{#!hs {-# LANGUAGE TemplateHaskell #-} import System.Environment ( getArgs, getProgName ) import Data.List ( intercalate ) import Data.Either ( partitionEithers ) import Language.Haskell.TH data Option = Foo | Bar | Baz deriving (Read, Show) -- If the next non-comment line is commented this will not compile: -- opts.hs:13:17: -- ‘Option’ is not in the type environment at a reify -- In the splice: -- $(do { ty <- reify ''Option; -- let showCon (NormalC n _) = ... -- showCon _ = ... -- ....; -- return . LitE . StringL $ intercalate ", " strs }) $(return []) allowedArgs :: String allowedArgs = $(do ty <- reify ''Option let showCon (NormalC n _) = nameBase n showCon _ = error "Can't handle non-normal constructors" strs = case ty of (TyConI (DataD _ _ _ cons _)) -> map showCon cons _ -> error "Can't handle non-tycon type" return . LitE . StringL $ intercalate ", " strs) main :: IO () main = do parsedArgs <- map parseArg `fmap` getArgs case partitionEithers parsedArgs of ([], okArgs) -> putStrLn $ "Computing with: " ++ show okArgs (badArgs, _) -> do progName <- getProgName putStrLn $ "Bad args: " ++ intercalate ", " badArgs putStrLn $ "Usage: " ++ progName ++ " " ++ allowedArgs where parseArg :: String -> Either String Option parseArg x = case reads x of [(o, "")] -> Right o _ -> Left $ show x }}} When I first wrote the program, I didn't need the `$(return [])` trick (using 7.6.3) and I was surprised that it broke upon upgrading to 7.8.3. In fact, I solved the problem by moving the declaration of `Option` to another module, but I still think it would be reasonable to allow it within the same declaration group, hence the proposed change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Really? With the `$(return [])` the above code works in 7.8, 7.10 and HEAD. I think. I'm a bit surprised it doesn't work without the `$(return [])`, because data types are typechecked before value declarations. But it doesn't. If that worked, would you be happy? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): I can confirm that with `$(return [])` the code compiles on 7.8.3 and 7.10.3. My issue is that the `$(return [])` trick seems to be just that, a trick, required to make GHC accept a program that naively appears reasonable. I was hoping to be able to make a (small, I thought) change to GHC to allow this program to work without the trick. I know this isn't the most-important issue, but I was hoping to find a small ticket to work on as a first go at hacking on GHC that a) I understand the need for (albeit perhaps minor!), and b) is reasonably small, so I don't bite off more than I can chew. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I also quite dislike `$(return [])` and support fixing this ticket. But I think your approach in comment:32 is quite a bit simpler than it may seem, because everything you say there is (I believe) already implemented except for point (5). In particular, GHC already does dependency analysis and chunking, and it would be terribly wrong not to have splicy things depend on everything else in the declaration group. The only problem, I believe, is that type-checking is held off until the whole group is renamed. (Splice action happens in the renamer.) It may or may not be hard to change that routing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): A small status update: this is tricky! Replying to [comment:37 goldfire]:
In particular, GHC already does dependency analysis and chunking, and it would be terribly wrong not to have splicy things depend on everything else in the declaration group.
I can't actually see that this is true for ''untyped'' splices! For ''typed'' splices I think it happens in the renamer, here: https://github.com/ghc/ghc/blob/master/compiler/rename/RnSplice.hs#L403 But I haven't found an equivalent for untyped splices.
The only problem, I believe, is that type-checking is held off until the whole group is renamed. (Splice action happens in the renamer.) It may or may not be hard to change that routing.
Yes, this is indeed the case. In particular, renaming of the group happens first, here: https://github.com/ghc/ghc/blob/master/compiler/typecheck/TcRnDriver.hs#L558 before type checking of the group's declarations happens later, here: https://github.com/ghc/ghc/blob/master/compiler/typecheck/TcRnDriver.hs#L596 Since `reify` is called during renaming, it fails since the type environments do not contain the names in question. I'm a bit stuck as to how to proceed! Perhaps the obvious question is: is there a particular reason to run untyped splices in the renamer vs the typechecker? I assume we can't do proper dependency analysis until after renaming, so I'm not sure it's possible to do the dependency sorting 'before' renaming (such that we could rename/typecheck non-splicy declarations before splicy declarations). If we could run untyped splices in the typechecker i.e. after renaming and dependency analysis, I assume we would be able to refer to names earlier in the dependency ordering. Any thoughts/advice that may get me unstuck? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:38 owst]:
Replying to [comment:37 goldfire]:
In particular, GHC already does dependency analysis and chunking, and it would be terribly wrong not to have splicy things depend on everything else in the declaration group.
I can't actually see that this is true for ''untyped'' splices!
I was referring to [https://github.com/ghc/ghc/blob/master/compiler/rename/RnBinds.hs#L293 this], which is about dependency analysis on bindings in general, not on splices.
Perhaps the obvious question is: is there a particular reason to run
untyped splices in the renamer vs the typechecker? See [wiki:TemplateHaskell/BlogPostChanges]. Splices used to be run in the typechecker. But that caused #4364. And, sadly, I don't know a way to solve #4364 and the current ticket. The plan from comment:32 implicitly assumes that deciding that two declarations are mutually recursive is a conservative choice, and so we can do it even when we're not sure that the declarations are indeed mutually recursive. But #4364 shows us that this is not the case -- mutual recursion is ''not'' conservative for type declarations. And it isn't really for term declarations either: when declarations are mutually recursive, type generalization happens ''after'' checking the whole group, and so making more definitions think that they are mutually recursive potentially reduces that level of polymorphism (don't have an example of this intricate interaction to hand, I'm afraid). So we seem to be a bit stuck: * Properly checking for mutual recursion requires that splices be run in the renamer. * The use of `reify` as proposed here requires that splices be run in the typechecker. We clearly can't have both. (Note that running the splices twice or something silly like that doesn't solve the problem, as the `reify` calls in the first run will fail.) I'm quite loathe to introduce something like `$$$(...)` to mean an-untyped-splice-that-runs-in-the-typechecker. But I could see having a `-frun-splices-in-typechecker` flag that solves this ticket but breaks #4364; users would just choose which behavior they prefer. (Yes, yes, I know: it would be nice to control this per-splice. Perhaps that would be better.) The downside to this approach is that it means duplicating much of the infrastructure that runs the splices. How bad a burden is this? Hard to know without implementing it. One potential problem: we really can't run ''pattern'' splices during type-checking, as they bring names into scope. So they would be exempted from the new behavior, beguiling users into perpetuity. (Red herring alert: Much of [wiki:TemplateHaskell/BlogPostChanges#Toostronglytyped] talks about the need to run ''quotes'' in the renamer. Anything discussed here would not change that behavior. This is only about ''splices''.) I'm increasingly worried about the power-to-weight ratio of this proposal. Recall that "weight" has two distinct components: 1. The amount of code (both lines and complexity) that this brings, which must be maintained forever. 2. The amount of cognitive burden this feature places on users trying to understand Template Haskell, which would now have two different modes of operation, both with very subtle, hard-to-predict consequences. I'm certainly not saying "no" to the proposal. But I, personally, would need convincing before agreeing to merge. A rising chorus of voices saying "I need this feature in order to use Haskell more successfully for my business or research" tends to be quite convincing. Or perhaps I've entirely mischaracterized the problem and there is an easier way to do all this. That would make me happy. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

I was referring to [https://github.com/ghc/ghc/blob/master/compiler/rename/RnBinds.hs#L293
See [wiki:TemplateHaskell/BlogPostChanges]. Splices used to be run in
So we seem to be a bit stuck:
[...] I'm increasingly worried about the power-to-weight ratio of this
#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:39 goldfire]: this], which is about dependency analysis on bindings in general, not on splices. Aha! Incidentally, the line linked is never reached for the failing testcase in the original report, since the line above it is where the splice is renamed, and the `reify` call fails. the typechecker. But that caused #4364. And, sadly, I don't know a way to solve #4364 and the current ticket. The plan from comment:32 implicitly assumes that deciding that two declarations are mutually recursive is a conservative choice, and so we can do it even when we're not sure that the declarations are indeed mutually recursive. But #4364 shows us that this is not the case -- mutual recursion is ''not'' conservative for type declarations. And it isn't really for term declarations either: when declarations are mutually recursive, type generalization happens ''after'' checking the whole group, and so making more definitions think that they are mutually recursive potentially reduces that level of polymorphism (don't have an example of this intricate interaction to hand, I'm afraid). Ah yes, a very good reason to move running of splices to the renamer. Thanks for pointing out the relevant ticket! proposal.
I agree, you're absolutely right about the power-to-weight ratio; bother! :-) Oh well, I've tweaked the manual so hopefully there might be a little less confusion about what's going on in this situation (and indeed, a pointer towards the `$(return [])` workaround). I'll try and move onto the next small ticket! Thanks for the discussion on this one, goldfire! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:40 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Oh, should we (I, if I can?) close this ticket, if we're not going to pursue it further development-wise, and the documentation change has been merged? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:41 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): In case it wasn't clear, until I wrote comment:39, I thought this was all quite feasible and a nice plan. I just don't want you to think I led you down a garden path into a trap! But falling into traps is just part of software development, I suppose. I'm grateful for your time and good attitude as this proposal has become pear-shaped. There's one important thing to do before closing the ticket: record our discoveries somewhere. In particular, I think a Note in the code is in order about why things are the way they are. Might you find a good spot, summarizing our discoveries and linking to this ticket? It might also be worth putting a link to this ticket in the manual, in case an overinterested soul wanders by. You say you've updated the manual. Where? How? Are you a committer? Or is there a Phab patch? (Apologies if the answer to this is obvious. It's even possible I have reviewed your changes and applied them myself! I tend to be rather aggressive in deleting stale records in my brain of tasks having been accomplished. This habit may sometimes make me appear somewhat dense. Sorry!) Once all that's done, we (you should be able to) should close this as wontfix. Thanks again for your efforts here, and I'm sorry that they didn't lead to fruition. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:42 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:42 goldfire]:
In case it wasn't clear, until I wrote comment:39, I thought this was all quite feasible and a nice plan. I just don't want you to think I led you down a garden path into a trap! But falling into traps is just part of software development, I suppose. I'm grateful for your time and good attitude as this proposal has become pear-shaped.
Indeed so that hidden traps are part of software development - thanks for helping me down (what appeared to be) a sensible path!
There's one important thing to do before closing the ticket: record our discoveries somewhere. In particular, I think a Note in the code is in order about why things are the way they are. Might you find a good spot, summarizing our discoveries and linking to this ticket? It might also be worth putting a link to this ticket in the manual, in case an overinterested soul wanders by.
Good idea, I'll try and do that this evening.
You say you've updated the manual. Where? How? Are you a committer? Or is there a Phab patch?
Yes, there's a Phab patch - see https://phabricator.haskell.org/D1899 - I 'think' I don't need to do anything further with that patch, correct? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:43 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): No, according to the Phab diff, that patch has been committed. Thanks. Just post a new Diff for the remaining changes when you're ready and link to it from here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:44 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:44 goldfire]:
No, according to the Phab diff, that patch has been committed. Thanks. Just post a new Diff for the remaining changes when you're ready and link to it from here.
Done - https://phabricator.haskell.org/D1985 - please let me know what you think! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:45 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 7.8.3 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => wontfix * milestone: => 8.2.1 Comment: Phab:D1899 was committed as http://git.haskell.org/ghc.git/commit/93e2c8fff902c12fd22d907f7648d847ebfd21.... Phab:D1985 was committed as http://git.haskell.org/ghc.git/commit/d48220eb7b2029ab90ea8185ac82b6bed51009.... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:46 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC