
#13973: NamedFieldPuns fails for qualified imports if field name is already in scope -------------------------------------+------------------------------------- Reporter: sergv | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hi, I get following error on the program below {{{ Package has never been configured. Configuring with default flags. If this fails, please run configure manually. Resolving dependencies... Configuring test-0.1.0.0... Building test-0.1.0.0... Preprocessing library test-0.1.0.0... [1 of 2] Compiling Record ( Record.hs, dist/build/Record.o ) [2 of 2] Compiling Test ( Test.hs, dist/build/Test.o ) <no location info>: error: ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): translateConPatVec: lookup Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} The cabal project: {{{ name: test version: 0.1.0.0 cabal-version: >= 1.16 build-type: Simple library exposed-modules: Record Test default-language: Haskell98 build-depends: base >= 4.7 }}} The module `Record.hs`: {{{#!hs module Record (Record(..)) where data Record = Record { field1 :: Int, field2 :: Int } }}} The main module `Test.hs`: {{{#!hs {-# LANGUAGE NamedFieldPuns #-} module Test (foo) where import qualified Record as Rec -- The culprit field2 :: () field2 = () foo :: Rec.Record -> Int foo Rec.Record{Rec.field1, field2} = field1 + field2 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13973 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler