[GHC] #9990: Top level module identifiers shadow imported identifiers

#9990: Top level module identifiers shadow imported identifiers -------------------------------------+------------------------------------- Reporter: drb226 | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Let's try this out as a language pragma and see if we like it? Artificial example: {{{#!hs {-# LANGUAGE TopLevelShadowsImports #-} import Data.Monoid (<>) = mappend main = putStrLn ("Hello" <> " " <> "World") }}} Current behavior: error: ambiguous occurrence of (<>) Desired behavior: uses top-level definition of (<>), prints "hello world" -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9990 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9990: Top level module identifiers shadow imported identifiers -------------------------------------+------------------------------------- Reporter: drb226 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): Even when such a pragma is active, I'd expect the shadow-warnings to be emitted -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9990#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9990: Top level module identifiers shadow imported identifiers -------------------------------------+------------------------------------- Reporter: drb226 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by alexey_r): Slight extension suggestion: include explicitly imported identifiers together with top-level identifiers. So: 1. if an identifier is imported both explicitly and implicitly, there is no ambiguity; 2. if an identifier is imported explicitly and defined at top-level, there is an ambiguity. Identifiers brought into scope by a `(..)` aren't considered explicitly imported for this purpose (otherwise extending a module could silently change meaning of an identifier). As a side effect, many uses of `hiding` would be no longer necessary. Of course, the pragma's name would have to be changed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9990#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9990: Top level module identifiers shadow imported identifiers -------------------------------------+------------------------------------- Reporter: drb226 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by drb226): Another idea is to make a per-binding pragma. {{{#!hs import Data.Monoid {-# SHADOWS (<>) #-} (<>) = mappend main = putStrLn ("Hello" <> " " <> "World") }}} This technique avoids unintended shadowing, intentionally resolves ambiguity by shadowing imports, and shouldn't need to set off the regular shadow warnings. This same technique could also be used to annotate imports: {{{#!hs import Foo {-# SHADOWS foo, Bar(..) #-} import OtherFoo }}} Just throwing that idea out there. Unlike `hiding`, the SHADOWS pragma could check to make sure that the replacement actually exists. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9990#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9990: Top level module identifiers shadow imported identifiers -------------------------------------+------------------------------------- Reporter: drb226 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by alexey_r): I've added an example of the problem with `(..)` in my comment above; so far as I can see, it applies to `SHADOWS` as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9990#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9990: Top level module identifiers shadow imported identifiers -------------------------------------+------------------------------------- Reporter: drb226 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by htebalaka): I wrote a proposal for the explicitly imported identifiers case here [1], which was discussed here [2]. #9702 is also relevant. [1] https://www.haskell.org/haskellwiki/PermissiveImportsProposal [2] https://www.haskell.org/pipermail/glasgow-haskell- users/2014-October/025306.html -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9990#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC