[GHC] #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- *Main> price Stock{name=name,ric=ric,price=price} = price ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-mingw32): translateConPatVec: lookup Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by wozgonon): * Attachment "bug.txt" added. Code typed into a WinCHCi window - bug at end -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by wozgonon): * failure: None/Unknown => Compile-time crash * os: Unknown/Multiple => Windows * architecture: Unknown/Multiple => x86_64 (amd64) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thank you. That's a long script -- might you be able to shrink it to a minimal test case? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by wozgonon): -- 1) Place code at the end of this comment into a source file: test.hs -- 2) In WinCHCI -- Prelude> :load test.hs -- *Main> price Stock{name=name,ric=ric,price=price} = price -- 3) Observe error message: -- ghc: panic! (the 'impossible' happened) -- (GHC version 8.0.1 for x86_64-unknown-mingw32): -- translateConPatVec: lookup -- -- Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug --test.hs data Stock = Stock {name :: String, ric :: String, price :: Float} deriving (Show) arm = Stock {name="ARM Holdings", ric="ARM.L", price=999} iii = Stock {name="3I Group PLC", ric="III.L", price=549} stockprice(Stock{name=name,ric=ric,price=price})=price type Holding = (Stock,Int) stock h= fst h shares h= snd h value h=stockprice(stock h)*fromIntegral(shares(h)) type Portfolio = [Holding] portfolio= [(arm, 198), (iii, 0)] list= map value portfolio -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by wozgonon): Actually, one can reproduce with just two lines: {{{ GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Prelude> data Stock = Stock {name :: String, ric :: String, price :: Float} deriving (Show) Prelude> price Stock{name=name,ric=ric,price=price} = price ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-mingw32): translateConPatVec: lookup Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Prelude> }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => PatternMatchWarnings * cc: gkaracha (added) * owner: => gkaracha Comment: George, might you look at this? It's in the pattern-match checker. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gkaracha): Replying to [comment:5 simonpj]:
George, might you look at this? It's in the pattern-match checker.
Yes, I will take a look. It seems that the usage of the same name makes the checker crash for some reason, since the following {{{#!hs price' Stock{name=n,ric=r,price=p} = p }}} does not crash. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gkaracha): Actually, the more I look at it, there is something wrong with the example: {{{ Prelude> data Stock = Stock {name :: String, ric :: String, price :: Float} Prelude> price Stock{name=name,ric=ric,price=price} = price }}} One should not even be allowed to define function `price` because it overlaps with the record field with the same name, so this must fail much earlier than desugaring (where the checker lives). Indeed, when I put the example in a file and load it I get: {{{ T12158.hs:7:1: error: Multiple declarations of ‘price’ Declared at: T12158.hs:5:53 T12158.hs:7:1 }}} which is correct. The only way to make this crash is if I type these two in ghci, which means that there is another bug (ghci accepting the program is the bug, it should fail during renaming). Additionally, the checker is perfectly happy with this: {{{ Prelude> data Stock = Stock {name :: String, ric :: String, price :: Float} Prelude> price2 Stock{name=name,ric=ric,price=price} = price }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Aha. Quite right. In general GHCi lets you over-ride an old definition for `f` with a new one. But here it doesn't make sense to override a record selector with a function. Someone should think this through. It's a bit fiddly, but I don't think it's really hard. Eg. in GHCi don't allow a let-binding override a record selector. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: roshats (added) * component: Compiler => GHCi * os: Windows => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple Comment: When you actually use a `let` binding though, it works fine: {{{ Prelude> data Stock = Stock {name :: String, ric :: String, price :: Float} Prelude> let price Stock{name=name,ric=ric,price=price} = price * 2 Prelude> price (Stock "abc" "def" 12.3) 24.6 }}} So this is another problem with the toplevel definitions feature introduced in GHCi 8.0 (#7253). See also #12091. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by p1neapple): Another variant with this or a related bug: Importing a data constructor with named fields, but only the constructor, and destructing an object of that; with another constructor of the same name as one not imported in scope also crashes GHC, see code, try to compile Test.hs: {{{determinize}}} leads to a panic. {{{ -- File NonDeterministicAutomaton.hs: {-# LANGUAGE GADTs #-} module NonDeterministicAutomaton where import qualified Data.Set as DS data NonDeterministicAutomaton s a where NA :: (Monoid s) => { delta :: DeltaProto a s, acc :: DS.Set s, states :: DS.Set s } -> NonDeterministicAutomaton s a type DeltaProto a s = a -> s -> DS.Set s }}} {{{ -- file Test.hs: {-# LANGUAGE GADTs #-} module Test where import Prelude hiding (map, filter) import NonDeterministicAutomaton (NonDeterministicAutomaton(NA)) import Data.Set data DeterministicAutomaton s a where DA :: (Monoid s) => { delta :: DeltaProto a s, acc :: Set s, states :: Set s } -> DeterministicAutomaton s a type DeltaProto a s = a -> s -> s determinize :: (Eq s, Ord s) => NonDeterministicAutomaton s a -> DeterministicAutomaton (Set s) a determinize ( NA { delta = delta0, acc = acc0, states = naStates } ) = DA delta' acc' (singleton naStates) where acc' = filter (\x -> any (`elem` x) acc0) (singleton naStates) delta' a s = empty }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * related: => #13644 Comment: The panic here is a duplicate of #13644. With the fix in Phab:D3988 I get: {{{ Prelude> data Stock = Stock {name :: String, ric :: String, price :: Float} Prelude> price Stock{name=name,ric=ric,price=price} = price <interactive>:2:31: error: • Constructor ‘Stock’ does not have field ‘price’ • In the pattern: Stock {name = name, ric = ric, price = price} In an equation for ‘price’: price Stock {name = name, ric = ric, price = price} = price Prelude> let price Stock{name=name,ric=ric,price=price} = price Prelude> }}} This is arguably still wrong, because if the explicit `let` binding works, the implicit one surely should work too. Presumably the GHCi name shadowing magic isn't quite consistent between the two cases. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by justus): I have another example of this error: {{{#!hs genExampleBenchmark :: Int -> LGCmdArgs -> [(String, Serialized)] genExampleBenchmark seed lgArgs@(LGCmdArgs { totalGraphs = total , language = lang , slowdatasource = slowDS , cachenum = cache , LG.percentages = p }) = ... }}} Here I use `LG.percentages` to disambiguate between two `percentages` record fields that are in scope, but it still fails with the same error. Btw if I remove the `LG.` it does throw the appropriate error telling me that it is an ambiguous reference. Commenting out `LG.percentages` makes the panic disappear. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup
-------------------------------------+-------------------------------------
Reporter: wozgonon | Owner: gkaracha
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.0.1
Resolution: | Keywords:
| PatternMatchWarnings
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: #13644 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): I may have struck this problem too. {{{ [34 of 59] Compiling Published.Bedford ( /flare-timing/earth/test-suite-earth/Published/Bedford.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-apple-darwin): translateConPatVec: lookup }}} This [[https://github.com/BlockScope/flare- timing/commit/07ea720ec98c9c756f7ed63ee7b80f574eb00a07|revision]] introduced the problem from which I was able to [[https://github.com/BlockScope/flare- timing/commit/b3963f61f97d0c70d726319260241bbedbe45f7f|workaround]] by using qualified imports. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * priority: normal => high * resolution: => duplicate * milestone: => 8.4.2 Old description:
*Main> price Stock{name=name,ric=ric,price=price} = price ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-mingw32): translateConPatVec: lookup
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
New description: {{{ *Main> price Stock{name=name,ric=ric,price=price} = price ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-mingw32): translateConPatVec: lookup Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Comment: If I understand correctly, this is a duplicate of #13644 which should be fixed in the soon-to-be-released 8.4.1. Perhaps someone could verify this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): I tried verifying this in place by updating stack to use [[https://gist.github.com/DanBurton/ba6fcf6b54491436fe8c98d2b2dc702b|ghc-8.4.1-alpha2]]. I set `allow-newer: true` and then hit problems with libraries that I worked through by adding specific packages references until I hit `refex- tdfa` that doesn't compile with this version of ghc. {{{ - location: git: https://github.com/haskell/primitive.git commit: 53f72ce69a4dfde5345cf5809a8b4a1993523367 extra-dep: true - location: git: https://github.com/haskell/text.git commit: 9fac5db9b048b7d68fa2fb68513ba86c791b3630 extra-dep: true - location: git: https://github.com/ChrisKuklewicz/regex-tdfa commit: f1b671946ee573f86d72484f3ab56487d456e735 }}} I think it may be better to try to get a minimal test case going with fewer dependencies. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): The minimal test case I ended up with seemed different enough to warrant its own case, see #14892. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12158#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC