[GHC] #15778: GHC HEAD-only panic (zonkTcTyVarToTyVar)

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler | Version: 8.5 (Type checker) | 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: -------------------------------------+------------------------------------- The following program typechecks on GHC 8.0.1 through 8.6.1: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind type a ~> b = a -> b -> Type type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 data family Sing (a :: k) data Flarble (a :: Type) where MkFlarble :: Flarble Bool data instance Sing (z :: Flarble a) where SMkFlarble :: Sing MkFlarble elimFlarble :: forall a (p :: forall x. Flarble x ~> Type) (f :: Flarble a). Sing f -> Apply p MkFlarble -> Apply p f elimFlarble s@SMkFlarble pMkFlarble = case s of (_ :: Sing (MkFlarble :: Flarble probablyABadIdea)) -> pMkFlarble }}} However, it panics on GHC HEAD: {{{ $ ~/Software/ghc/inplace/bin/ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.7.20181015 for x86_64-unknown-linux): zonkTcTyVarToTyVar probablyABadIdea_aWn[tau:2] Bool Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcMType.hs:1627:34 in ghc:TcMType }}} If I replace `probablyABadIdea` with `Bool`, then it typechecks again. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * version: 8.5 => 8.7 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This regression was introduced in commit 4d91cabcd5e3c603997d9876f6d30204a9b029c6 (`Allow scoped type variables refer to types`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: | Keywords: TypeInType 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => TypeInType Comment: Marginally simpler example: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind data Flarble (a :: Type) where MkFlarble :: Flarble Bool data SFlarble (z :: Flarble a) where SMkFlarble :: SFlarble MkFlarble foo :: SFlarble z -> () foo s@SMkFlarble = case s of (_ :: SFlarble (MkFlarble :: Flarble probablyABadIdea)) -> () }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: | Keywords: TypeInType 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The following code does //not// compile on earlier versions of GHC, but it is the simplest way to trigger the panic that I've discovered: {{{#!hs {-# LANGUAGE PolyKinds, ScopedTypeVariables #-} foo (_ :: (a :: probablyABadIdea)) = () }}} {{{ $ /opt/ghc/head/bin/ghc Bug.hs [1 of 1] Compiling Main ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.7.20181015 for x86_64-unknown-linux): zonkTcTyVarToTyVar probablyABadIdea_arQ[tau:1] TYPE t_arX[tau:1] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcMType.hs:1627:34 in ghc:TcMType }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: | Keywords: TypeInType 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: | -------------------------------------+------------------------------------- Comment (by simonpj): I know what is happening here. In `tcHsPatSigType` we have {{{ mk_tv_pair tv = do { tv' <- zonkTcTyVarToTyVar tv ; return (tyVarName tv, tv') } }}} But now the tyvar might have unified with a ''type'' not a type ''variable''. And in these cases it does. I think that the right thing is simply to remove the zonk. I'll act on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.8.1
Component: Compiler (Type | Version: 8.7
checker) |
Resolution: | Keywords: TypeInType
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: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T15778 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_compile/T15778 * status: new => merge Comment: Thanks! fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T15778 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: merge => closed * resolution: => fixed Comment: This shouldn't be merged. This fix relies on commit 4d91cabcd5e3c603997d9876f6d30204a9b029c6, which wasn't merged to the 8.6 branch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC