#5708: Qualified name in binding position
------------------------------+---------------------------------------------
Reporter: fryguybob | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Testcase:
Blockedby: | Blocking:
Related: |
------------------------------+---------------------------------------------
When building `diagrams` with HEAD I ran into this difference from 7.0.2
(and I believe 7.2) shown with this:
{{{
---- Qual.hs --------
{-# LANGUAGE TypeFamilies #-}
import qualified Blah.A as A
instance A.B Int where
type A.T Int = Bool
}}}
{{{
---- Blah/A.hs --------
{-# LANGUAGE TypeFamilies #-}
module Blah.A (B(..)) where
class B a where
type T a :: *
}}}
{{{
--- Output from HEAD (was same with 7.3.20111206)
$ ~/ghc/inplace/bin/ghc-stage2 --interactive Qual.hs
GHCi, version 7.5.20111215: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 2] Compiling Blah.A ( Blah/A.hs, interpreted )
[2 of 2] Compiling Main ( Qual.hs, interpreted )
Qual.hs:6:8: Qualified name in binding position: A.T
Failed, modules loaded: Blah.A.
*Blah.A>
}}}
{{{
---- Output from 7.0.2
$ ghci Qual.hs
GHCi, version 7.0.2: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 2] Compiling Blah.A ( Blah/A.hs, interpreted )
[2 of 2] Compiling Main ( qual.hs, interpreted )
Ok, modules loaded: Blah.A, Main.
*Main>
}}}
In our case we didn't need the qualified import anyway and removed it
here: http://www.patch-tag.com/r/byorgey/diagrams-
core/snapshot/hash/20111215185451-1e371-dcaeff70fc825e9afa91addbeaaa69c5749f5529/patch
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5708>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs