[GHC] #10897: Incorrect ASSERT for buildPatSyn

#10897: Incorrect ASSERT for buildPatSyn -------------------------------------+------------------------------------- Reporter: ezyang | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Consider the following two files: {{{ -- A.hs {-# LANGUAGE PatternSynonyms #-} module A where pattern Single :: a -> a pattern Single x = x -- B.hs module B where import A Single y = True }}} When I build these using one-shot compilation using a debugged GHC (i.e. with ASSERTs) I get the following error: {{{ [ezyang@hs01 ghc-quick3]$ inplace/bin/ghc-stage2 -c A.hs -fforce-recomp [ezyang@hs01 ghc-quick3]$ inplace/bin/ghc-stage2 -c B.hs -fforce-recomp ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150918 for x86_64-unknown-linux): ASSERT failed! file compiler/iface/BuildTyCl.hs, line 210 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I expanded the assert and discovered it was claiming the universal type variables of the matcher should be equal to the type variables of the pattern declaration. This assert cannot possibly be right: the matcher and the pattern declaration are typechecked separately and there's no reason that the local binders should actually be the same. The equality test here should be done up to alpha-renaming. The other thing I found a bit puzzling was whether or not it mattered whether or not we used the local type variables from the matcher or the freshly bound ones. I suppose if we are consistent it shouldn't matter, so I don't think the code is buggy, just a bad ASSERT. BTW: this assert problem doesn't show up with `--make` because the assert occurs during typechecking of interface files, and with `--make` we don't need to typecheck an interface file. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10897 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10897: Incorrect ASSERT for buildPatSyn -------------------------------------+------------------------------------- Reporter: ezyang | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by cactus): Without having looked at the details yet, I'd just like to mention that the reason I've put those `ASSERT`s in is because the plan, at one point, was to eventually get rid of most arguments to `buildPatSyn` and just reconstruct them from the `matcher`'s `idType`. Unfortunately, I can't remember off-hand why that wasn't feasible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10897#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10897: Incorrect ASSERT for buildPatSyn -------------------------------------+------------------------------------- Reporter: ezyang | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by cactus): * keywords: => PatternSynonyms -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10897#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10897: Incorrect ASSERT for buildPatSyn -------------------------------------+------------------------------------- Reporter: ezyang | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by cactus): Hmm, it's starting to come back -- all those `ifPat*` type fields of `IfacePatSyn` are needed so that we can implement `pprIfaceDecl` and `freeNamesIfDecl` without the ability to turn the `IfExtName` of `ifPatMatcher` into a proper `Id`. That suggests we should look into it a bit more to see if it's valid when these self-confessed redundant fields aren't actually the same as the types recovered from the `Id` of the matcher. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10897#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10897: Incorrect ASSERT for buildPatSyn
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner: cactus
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.11
checker) | Keywords:
Resolution: | PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
-------------------------------------+-------------------------------------
Comment (by Matthew Pickering

#10897: Incorrect ASSERT for buildPatSyn -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: patsyn/T10897 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * owner: cactus => * testcase: => patsyn/T10897 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10897#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10897: Incorrect ASSERT for buildPatSyn -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: patsyn/T10897 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): For me this fails with {{{ Declaration for Single: Iface type variable out of scope: t Cannot continue after interface file error }}} I've had a poke around but the interface file stuff is a complete mystery for me. Someone else with more experience will have to look. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10897#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10897: Incorrect ASSERT for buildPatSyn
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.11
checker) | Keywords:
Resolution: | PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case: patsyn/T10897
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10897: Incorrect ASSERT for buildPatSyn -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: fixed | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: patsyn/T10897 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Works fine now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10897#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC