[GHC] #8011: -ddump-minimal-imports creates incorrect imports for associated types

#8011: -ddump-minimal-imports creates incorrect imports for associated types -----------------------------+---------------------------------------------- Reporter: dsf | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- If you have a module URL.hs: {{{ {-# LANGUAGE TypeFamilies #-} module URL (ToURL(toURL, nullURL, errorURL), URLT) where class ToURL a where type URLT a toURL :: a -> URLT a nullURL :: a errorURL :: a -> URLT a }}} And a module that uses it Tmp.hs: {{{ {-# LANGUAGE FlexibleContexts #-} module Tmp ( clean ) where import Data.Char (isAlphaNum) import Data.List (dropWhile) import URL clean :: (ToURL url, Show (URLT url)) => url -> String clean = filter isAlphaNum . show . toURL }}} when you run {{{ghc -ddump-minimal-imports Tmp.hs}}} the resulting {{{Tmp.imports}}} will contain the line {{{ import URL ( ToURL(URLT, toURL) ) }}} but it should contain {{{ import URL ( ToURL(toURL), URLT ) }}} This affects both associated type and associated type synonym declarations. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8011 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8011: -ddump-minimal-imports creates incorrect imports for associated types
-----------------------------+----------------------------------------------
Reporter: dsf | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.6.3 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Blockedby:
Blocking: | Related:
-----------------------------+----------------------------------------------
Comment(by simonpj@…):
commit e662c62ec8621c66569d74cca7d3a3f648876b8c
{{{
Author: Simon Peyton Jones

#8011: -ddump-minimal-imports creates incorrect imports for associated types
-------------------------------------------+--------------------------------
Reporter: dsf | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: fixed | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Difficulty: Unknown
Testcase: indexed_types/should_compile | Blockedby:
Blocking: | Related:
-------------------------------------------+--------------------------------
Changes (by simonpj):
* status: new => closed
* difficulty: => Unknown
* resolution: => fixed
* testcase: => indexed_types/should_compile
Comment:
Actually I found that a further change was needed to allow
{{{
module URL ( ToURL(toURL, nullURL, errorURL, URLT) ) where ...
}}}
Notice the associated type `URLT` can be a sub-component of the
`ToURL(...)` list.
The patch is this:
{{{
commit 0cb60cee510ac65b06d9c5b1b3ea8bc9984f6f33
Author: Simon Peyton Jones
---------------------------------------------------------------
compiler/rename/RnNames.lhs | 66 +++++++++++++++++++-------------------------- 1 file changed, 27 insertions(+), 39 deletions(-) }}} Regression test tests both. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8011#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC