[GHC] #15666: Dependent type synonym in recursive type family causes GHC to panic

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 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: -------------------------------------+------------------------------------- = Background I had written the following code in Haskell (GHC): {{{#!hs {-# LANGUAGE NoImplicitPrelude, TypeInType, PolyKinds, DataKinds, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-} import Data.Kind(Type) data PolyType k (t :: k) type Wrap (t :: k) = PolyType k t type Unwrap pt = (GetType pt :: GetKind pt) type family GetKind (pt :: Type) :: Type where GetKind (PolyType k t) = k type family GetType (pt :: Type) :: k where GetType (PolyType k t) = t }}} The intention of this code is to allow me to wrap a type of an arbitrary kind into a type (namely `PolyType`) of a single kind (namely `Type`) and then reverse the process (i.e. unwrap it) later. = Problem I wanted to define a function that would recursively operate on a composite type like so: {{{#!hs data Composite :: a -> b -> Type type family RecursiveWrap (expr :: exprK) where RecursiveWrap (Composite a b) = Wrap (Composite (Unwrap (RecursiveWrap a)) (Unwrap (RecursiveWrap b))) RecursiveWrap x = Wrap x }}} However, the above definition causes GHC to panic: {{{ ghc.exe: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-unknown-mingw32): cyclic evaluation in fixIO }}} = Ideas If we inline the the `Unwrap` synoynm into the defintion of the type family above like so: {{{#!hs type family RecursiveWrap expr where RecursiveWrap (Composite a b) = Wrap (Composite (GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a)) (GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a)) ) RecursiveWrap x = Wrap x }}} GHC instead simply produces an error: {{{ * Type constructor `RecursiveWrap' cannot be used here (it is defined and used in the same recursive group) * In the first argument of `GetKind', namely `(RecursiveWrap a)' In the kind `GetKind (RecursiveWrap a)' In the first argument of `Composite', namely `(GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a))' }}} As such, I suspect this has to do with the recursive type family appearing in the kind signature when the `Unwrap` type synonym is expanded. However, it strikes me as odd that even the above code errors. Since with the `UndecidableInstances` extension turned on, I think that I should be able to write recursive type families like the above. Especially given that the above family would not loop indefinitely and thus be reducible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: newcomer 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 tydeu): * keywords: => newcomer -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: newcomer 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: | -------------------------------------+------------------------------------- Old description:
= Background
I had written the following code in Haskell (GHC):
{{{#!hs {-# LANGUAGE NoImplicitPrelude, TypeInType, PolyKinds, DataKinds, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
import Data.Kind(Type)
data PolyType k (t :: k)
type Wrap (t :: k) = PolyType k t type Unwrap pt = (GetType pt :: GetKind pt)
type family GetKind (pt :: Type) :: Type where GetKind (PolyType k t) = k
type family GetType (pt :: Type) :: k where GetType (PolyType k t) = t }}}
The intention of this code is to allow me to wrap a type of an arbitrary kind into a type (namely `PolyType`) of a single kind (namely `Type`) and then reverse the process (i.e. unwrap it) later.
= Problem
I wanted to define a function that would recursively operate on a composite type like so:
{{{#!hs data Composite :: a -> b -> Type
type family RecursiveWrap (expr :: exprK) where RecursiveWrap (Composite a b) = Wrap (Composite (Unwrap (RecursiveWrap a)) (Unwrap (RecursiveWrap b))) RecursiveWrap x = Wrap x }}}
However, the above definition causes GHC to panic:
{{{ ghc.exe: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-unknown-mingw32): cyclic evaluation in fixIO }}}
= Ideas
If we inline the the `Unwrap` synoynm into the defintion of the type family above like so:
{{{#!hs type family RecursiveWrap expr where RecursiveWrap (Composite a b) = Wrap (Composite (GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a)) (GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a)) ) RecursiveWrap x = Wrap x }}}
GHC instead simply produces an error:
{{{ * Type constructor `RecursiveWrap' cannot be used here (it is defined and used in the same recursive group) * In the first argument of `GetKind', namely `(RecursiveWrap a)' In the kind `GetKind (RecursiveWrap a)' In the first argument of `Composite', namely `(GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a))' }}}
As such, I suspect this has to do with the recursive type family appearing in the kind signature when the `Unwrap` type synonym is expanded.
However, it strikes me as odd that even the above code errors. Since with the `UndecidableInstances` extension turned on, I think that I should be able to write recursive type families like the above. Especially given that the above family would not loop indefinitely and thus be reducible.
New description: = Background I had written the following code in Haskell (GHC): {{{#!hs {-# LANGUAGE NoImplicitPrelude, TypeInType, PolyKinds, DataKinds, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-} import Data.Kind(Type) data PolyType k (t :: k) type Wrap (t :: k) = PolyType k t type Unwrap pt = (GetType pt :: GetKind pt) type family GetKind (pt :: Type) :: Type where GetKind (PolyType k t) = k type family GetType (pt :: Type) :: k where GetType (PolyType k t) = t }}} The intention of this code is to allow me to wrap a type of an arbitrary kind into a type (namely `PolyType`) of a single kind (namely `Type`) and then reverse the process (i.e. unwrap it) later. = Problem I wanted to define a function that would recursively operate on a composite type like so: {{{#!hs data Composite :: a -> b -> Type type family RecursiveWrap expr where RecursiveWrap (Composite a b) = Wrap (Composite (Unwrap (RecursiveWrap a)) (Unwrap (RecursiveWrap b))) RecursiveWrap x = Wrap x }}} However, the above definition causes GHC to panic: {{{ ghc.exe: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-unknown-mingw32): cyclic evaluation in fixIO }}} = Ideas If we inline the the `Unwrap` synoynm into the defintion of the type family above like so: {{{#!hs type family RecursiveWrap expr where RecursiveWrap (Composite a b) = Wrap (Composite (GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a)) (GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a)) ) RecursiveWrap x = Wrap x }}} GHC instead simply produces an error: {{{ * Type constructor `RecursiveWrap' cannot be used here (it is defined and used in the same recursive group) * In the first argument of `GetKind', namely `(RecursiveWrap a)' In the kind `GetKind (RecursiveWrap a)' In the first argument of `Composite', namely `(GetType (RecursiveWrap a) :: GetKind (RecursiveWrap a))' }}} As such, I suspect this has to do with the recursive type family appearing in the kind signature when the `Unwrap` type synonym is expanded. However, it strikes me as odd that even the above code errors. Since with the `UndecidableInstances` extension turned on, I think that I should be able to write recursive type families like the above. Especially given that the above family would not loop indefinitely and thus be reducible. -- Comment (by tydeu): Realized I accidentally broke my example while trying to clean it up for this ticket. Fixed it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: newcomer 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 appears to be fixed as of GHC 8.6.1 (it's not immediately clear which commit fixed this issue). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: newcomer 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 tydeu): Replying to [comment:3 RyanGlScott]:
This appears to be fixed as of GHC 8.6.1 (it's not immediately clear which commit fixed this issue).
I just tested this and yes, the issue has been resolved. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 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 potato44): * keywords: newcomer => Comment: The newcomer label is for when a newcomer (to GHC's codebase) should be able to fix the bug, not for the reporter being a newcomer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 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 tydeu): Replying to [comment:5 potato44]:
The newcomer label is for when a newcomer (to GHC's codebase) should be able to fix the bug, not for the reporter being a newcomer.
Ah, I'll keep that in mind. My apologies. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #15380 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #15380 Comment: Ah, the commit that fixed this is 59f38587d44efd00b10a6d98f6a7a1b22e87f13a (`Remove the type-checking knot.`) That being said, the program in this ticket is rather different from the one in #15380 (which that commit fixed), since this ticket's program actually does compile. I'll add a separate regression test for this one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15666: Dependent type synonym in recursive type family causes GHC to panic
-------------------------------------+-------------------------------------
Reporter: tydeu | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: #15380 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#15666: Dependent type synonym in recursive type family causes GHC to panic -------------------------------------+------------------------------------- Reporter: tydeu | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | dependent/should_compile/T15666 Blocked By: | Blocking: Related Tickets: #15380 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * testcase: => dependent/should_compile/T15666 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15666#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC