
#15380: Infinite typechecker loop in GHC 8.6 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 (Type checker) | Keywords: TypeInType, | Operating System: Unknown/Multiple TypeFamilies | Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program loops infinitely during typechecking with GHC 8.6.1 and HEAD: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind class Generic a where type Rep a :: Type class PGeneric a where type To a (x :: Rep a) :: a type family MDefault (x :: a) :: a where MDefault x = To (M x) class C a where type M (x :: a) :: a type M (x :: a) = MDefault x }}} In GHC 8.4.3, however this fails with a proper error: {{{ $ /opt/ghc/8.4.3/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:15:16: error: • Occurs check: cannot construct the infinite kind: a ~ Rep (M x) -> M x • In the type ‘To (M x)’ In the type family declaration for ‘MDefault’ • Type variable kinds: x :: a | 15 | MDefault x = To (M x) | ^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15380 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler