[GHC] #8570: In a pattern binding:ghc: panic! (the 'impossible' happened): Bogus selector Id
GHC
ghc-devs at haskell.org
Thu Nov 28 16:52:34 UTC 2013
#8570: In a pattern binding:ghc: panic! (the 'impossible' happened): Bogus
selector Id
---------------------------------------+----------------------------------
Reporter: rzetterberg | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: Compile-time crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
---------------------------------------+----------------------------------
Comment (by simonpj):
I can't reproduce this. Here are the modules I used. I used these
modules:
{{{
module T8570a where
data Image = Image
{ id :: Integer
, categoryId :: Integer
, name :: String
, filepath :: String
} deriving (Show)
module T8570b where
data Field
= Password String
| Image Int
module T8570 where
import T8570a (Image(filepath))
import T8570b (Field(..))
foo logo = fp where Image{filepath = fp} = logo
}}}
I compiled thus:
{{{
bash$ ghc -c T8570a.hs
bash$ ghc -c T8570b.hs
bash$ ghc -c T8570.hs
T8570.hs:6:27:
Constructor `Image' does not have field `filepath'
In the pattern: Image {filepath = fp}
In a pattern binding: Image {filepath = fp} = logo
In an equation for `foo':
foo logo
= fp
where
Image {filepath = fp} = logo
}}}
I tried with ghc-7.6.3 and HEAD. They all work fine.
Can you offer a precise, reproducible test case? Thanks
Simon
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8570#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list