[GHC] #9778: Namespace collision detection for promoted types

GHC ghc-devs at haskell.org
Thu Nov 6 17:04:27 UTC 2014


#9778: Namespace collision detection for promoted types
-------------------------------------+-------------------------------------
              Reporter:  crockeea    |            Owner:
                  Type:  feature     |           Status:  new
  request                            |        Milestone:
              Priority:  normal      |          Version:  7.8.3
             Component:  Compiler    |         Keywords:
            Resolution:              |     Architecture:  Unknown/Multiple
      Operating System:              |       Difficulty:  Unknown
  Unknown/Multiple                   |       Blocked By:
       Type of failure:              |  Related Tickets:
  None/Unknown                       |
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
Description changed by crockeea:

Old description:

> In the following example
> {{{#!hs
> {-# LANGUAGE DataKinds #-}
>
> module Foo where
>
> data Nat = Z | S Nat
>
> data S
>
> foo :: S n -> S n
> foo = id
> }}}
>
> GHC displays the error
>
> {{{
> Foo.hs:12:8:
>     ‘S’ is applied to too many type arguments
>     In the type signature for ‘foo’: foo :: S n -> S n
> Failed, modules loaded: none.
> }}}
> Although it's clear in my example where the problem is, this example was
> distilled from a case where I imported module1 with type `S` defined and
> module2 with the promoted type `S`, which is what I was trying to use.
> Can we get namespace collision detection instead? Something like:
>
> {{{
> Foo.hs:9:15
> Ambiguous occurence ‘S’
> It could refer to either Foo.S defined at Foo.hs:7:1
>                       or to the promoted constructor S defined at
> Foo.hs:5:16
> Use 'S to refer to the promoted constructor.
> }}}

New description:

 In the following example
 {{{#!hs
 {-# LANGUAGE DataKinds #-}

 module Foo where

 data Nat = Z | S Nat

 data S

 foo :: S n -> S n
 foo = id
 }}}

 GHC displays the error

 {{{
 Foo.hs:12:8:
     ‘S’ is applied to too many type arguments
     In the type signature for ‘foo’: foo :: S n -> S n
 Failed, modules loaded: none.
 }}}

 Of course this code compiles without the definition of `data S`. Without
 namespace collision detection, it is easy to have working code, and then
 import a module which breaks the code. For example, I made this request
 after I imported Module1 with type `S` defined and Module2 with the
 promoted type `S`, which is what I was trying to use.

 Can we get namespace collision detection instead? I'm proposing something
 like:

 {{{
 Foo.hs:9:15
     Ambiguous occurence ‘S’
     It could refer to either Foo.S defined at Foo.hs:7:1
                           or to Foo.'S promoted from the constructor
 defined at Foo.hs:5:16
                           or to `Bar.'S` promoted from the constructor
 defined at Bar.hs:line#:char#
                           or to ...
     Use 'S to refer to promoted constructors.
 }}}

--

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


More information about the ghc-tickets mailing list