[GHC] #11432: Cannot export operator newtype

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeOperators #-} module Main (main, (-.->)(..)) where main :: IO () main = return () newtype (f -.-> g) a = Fn { apFn :: f a -> g a } }}} Fails to compile with {{{ [1 of 1] Compiling Main ( fn.hs, interpreted ) fn.hs:2:20: error: Not in scope: ‘-.->’ fn.hs:2:20: error: The export item ‘(-.->)(..)’ attempts to export constructors or class methods that are not visible here }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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 kosmikus): * cc: kosmikus (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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 bgamari): * priority: normal => highest * milestone: => 8.0.1 Comment: This is a regression relative to 7.10.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: mpickering Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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 mpickering): * owner: => mpickering Comment: This is a problem in the parser. Workaround, use the `type` keyword. {{{ {-# LANGUAGE TypeOperators #-} module T11432 (type (-.->)(..)) where newtype (f -.-> g) a = Fn { apFn :: f a -> g a } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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 mpickering): * owner: mpickering => Comment: I can't work out how to fix this. The problem is that (-.->) is put into the variable namespace rather than the type constructor namespace. However, I change the parsing rules to how they were in ghc-7.10.3 and it still doesn't accept it. Maybe that commit is responsible but I'm not sure anymore. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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): * cc: skvadrik (added) Comment: skvadrik: maybe you can have a look, as the author of the commit mentioned in comment:3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by goldfire): There's not going to be an easy solution to this. The problem is that we only know that `(-.->)` is a type when we see the open parenthesis after it. But the parser has only one-token lookahead. I would actually say that the current behavior -- requiring `type` -- is correct. We then have a rule that's simple for both parsers and people: any symbol not beginning with a `:` is assumed to be a variable, not a type. Note that we don't need to worry about standards-compliance here, as `TypeOperators` is not standardized. If it doesn't already, `TypeOperators` should imply `ExplicitNamespaces`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): As `Note [Type constructors in export list]` says, type/variable constructors in export lists introduce ambiguity in grammar: {{{ Mixing type constructors and variable constructors in export lists introduces ambiguity in grammar: e.g. (*) may be both a type constuctor and a function. -XExplicitNamespaces allows to disambiguate by explicitly prefixing type constructors with 'type' keyword. This ambiguity causes reduce/reduce conflicts in parser, which are always resolved in favour of variable constructors. To get rid of conflicts we demand that ambigous type constructors (those, which are formed by the same productions as variable constructors) are always prefixed with 'type' keyword. Unambigous type constructors may occur both with or without 'type' keyword. }}} Resolving ambiguity by changing grammar is impractical: type/variable constructors in export lists are used in exactly the same context (it's *not* a lookahead problem). This ambiguity can be resolved, but not on parser level: parser should parse constructor as 'just some constructor' (wrap it) and delay the actual decision to the next phase. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): The fact that GHC handled this ambiguous case correctly suggests that it already has this wrapping-delaying mechanism (because happy-generated parser always resolved the ambiguity in favor of variable constructor, which in this case is incorrect). I'll try to find out how it worked. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): Turns out I was wrong in thinking that variable/type constructors appear in the same context: `(..)` is only allowed after type constructors (so goldfire was right about parenthesis and lookahead). GHC grammar allows invalid syntax like `(..)` after variable constructors: https://ghc.haskell.org/trac/ghc/browser/ghc/compiler/parser/Parser.y#L633 {{{ export :: { OrdList (LIE RdrName) } : qcname_ext export_subspec {% mkModuleImpExp $1 (snd $ unLoc $2) ... }}} `qcname_ext` here can be both variable/type constructor, and `export_subspec` can be `(..)`. This can (and should) be fixed in grammar so that non-ambiguous constructs like `(-.->)(..)` in export lists are accepted without `type` keyword. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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 skvadrik): * Attachment "Parser.diff" added. Parser patch that disambiguates exported variable/type constructors by their subexport -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by thomie): Great. Could you please submit it to [wiki:Phabricator], like you did with your previous patch. Then it gets validated automatically (at least, if the buildbot is not over capacity at the time you submit). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): I see two possible ways to resolve this issue. * The first way is to change GHC grammar (as shown in attached Parser.diff) to distinguish between `(-.->)` and `(-.->)(..)` in export lists: the first construct must be recognized as variable constructor, while the second must be type constructor (because it has `(..)`). With this patch GHC can parse the reported program (and passes all existing tests). Note that the patch does not add any new conflicts. However, it is ugly: one has to lift low-level nonterminals (variable and type names) all the way up to export lists: parser cannot decide whether it is variable or type name until it sees subexport. * The second way (I have no example patch yet) would be to free grammar of all this mess: parse any constructor in export list as just some constructor (probably with subexport) and decide which kind it is later. So you see, this patch is kind of a demonstration that LALR grammars are capable of parsing such things. I'm not happy with this solution; I'd rather try the second way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by thomie): Ah, ok. Take your time. For your final patch, please add the example from the description as a test, see [wiki:Building/RunningTests/Adding], or look at an existing example in `testsuite/tests/parser`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): Sure! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by bgamari): If option (2) isn't feasible I think I'd prefer to require the user to specify an explicit namespace over option (1). The parser is already quite complex; adding more complexity for a case that is arguably more clear if written explicitly doesn't seem worthwhile to me. That is just my two cents, however. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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 bgamari): * owner: => skvadrik -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): I definitely agree that parser is already complicated enough. I think option (2) is not hard to implement, only I'll be away from home until 6th February and hardly have any time to look into it (it doesn't mean that I've given up). Apologies for the delay! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): slyfox helped me git-bisect the bug and it turns out that the faulty commit is ffc21506894c7887d3620423aaf86bc6113a1071. Commit message says: {{{ - I found that the parser was parsing an import item like T( .. ) as a *data constructor* T, and then using setRdrNameSpace to fix it. Stupid! So I changed the parser to parse a *type constructor* T, which means less use of setRdrNameSpace. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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 skvadrik): * Attachment "bisect.log" added. git-bisect log -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by mpickering): So * Revert the relevant part of that commit * Add a test * Add a note explaining why it is parsed as a data constructor rather than a type constructor? Will that fix the problem? Does that sound like a reasonable plan? Do you want to take care of it skvardrik? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Well `(-.->)` isn't (lexically) a data constructor either, so I have no idea why it worked before the commit but not after. If we understand why it worked before, we'd have a better chance of not messing something else up. I see {{{ qcname :: { Located RdrName } -- Variable or type constructor : qvar { $1 } | oqtycon_no_varcon { $1 } -- see Note [Type constructors in export list] }}} so obviously look carefully at that `Note` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): I think `-.->` is lexically `@varsym` (and `VARSYM` parser) and `(-.->)` is parsed as `'(' VARSYM ')'`: {{{ ... qcname -> qvar -> '(' varsym ')' -> '(' varsym_no_minus ')' -> '(' VARSYM ')' }}} I don't know yet why it did work before commit ffc21506894c7887d3620423aaf86bc6113a1071, but I suspect the answer is hidden not in grammar, but in the way data constructors are (were?) "fixed" after parsing to become type constructors. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): Simply reverting the relevant part of grammar does not work (even if it did, the fix is spurious). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Comment (by skvadrik): Replying to [comment:18 mpickering]:
Do you want to take care of it skvardrik? Yes, it will take me some time to make the right fix though.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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:D1888 Wiki Page: | -------------------------------------+------------------------------------- Changes (by skvadrik): * differential: => Phab:D1888 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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:D1888 Wiki Page: | -------------------------------------+------------------------------------- Comment (by skvadrik): So the breakage was **not** caused by the change of grammar (`(-.->)(..)` is parsed as neither `qcon` nor `oqtycon`, it is parsed as `qvar`). It was caused by removal of `setRdrNameSpace` call. D1888 breaks one test (`make test TEST=mod89`): we get error instead of warning and the message is different (perhaps less informative). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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:D1888 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Simon M and I are really doubtful about whether fixing this is a good idea at all. With the proposed fix we have {{{ module M( (%%)( A, B ) ) where -- OK data (%%) x y = A x | B y module M( (%%)( .. ) ) where -- OK data (%%) x y = A x | B y module M( (%%) ) where -- NOT OK data (%%) x y = A x | B y }}} This seems horribly non-uniform. Better just to require the `type` keyword in all three cases, I suggest. Very sorry not to have paid more attention before. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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:D1888 Wiki Page: | -------------------------------------+------------------------------------- Comment (by skvadrik): I agree that basing compilation decisions on subtle syntax changes is bad, but error message {{{ error: Not in scope: ‘%%’ }}} which appears suddenly after GHC upgrade is obscure. I think it should at least suggest the cause of error and the way to fix it. Perhaps something like this (don't hesitate to suggest a better wording): {{{ error: Not in scope: ‘%%’ Note: if '%%' is a type constructor, add 'type' keyword: 'type (%%)' (requires extension TypeOperators) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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:D1888 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm fine with a better error message. It would be Much Better if the "note" part only came out if there ''actually was'' a type constructor `(%%)` in scope. And that should be easy to check. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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:D1902 Wiki Page: | -------------------------------------+------------------------------------- Changes (by skvadrik): * differential: Phab:D1888 => Phab:D1902 Comment: Replying to [comment:27 simonpj]:
I'm fine with a better error message.
It would be Much Better if the "note" part only came out if there ''actually was'' a type constructor `(%%)` in scope. And that should be easy to check.
Done, please have a look at D1902. Message example: {{{ Not in scope: ‘-.->’ Note: use ‘type’ keyword to export type constructor ‘-.->’ defined at T11432.hs:9:1 (requires TypeOperators extension) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype
-------------------------------------+-------------------------------------
Reporter: phadej | Owner: skvadrik
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc1
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:D1902
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1902 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: 8.0.1 => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1902 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.0.1 Comment: Merged to `ghc-8.0` as d2744a3eb6457aa4043986c20685b9ecf8953612. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11432#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11432: Cannot export operator newtype
-------------------------------------+-------------------------------------
Reporter: phadej | Owner: skvadrik
Type: bug | Status: closed
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1902
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari
participants (1)
-
GHC