[GHC] #14723: GHC 8.4.1-alpha loops infinitely when typechecking

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This issue prevents `jvm-streaming` from compiling with GHC 8.4.1-alpha2. Here is my best attempt at minimizing the issue: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Bug () where import Data.Kind (Type) import Data.Proxy (Proxy(..)) import Data.String (fromString) import Data.Int (Int64) import GHC.Stack (HasCallStack) import GHC.TypeLits (Nat, Symbol) data JType = Iface Symbol data J (a :: JType) newIterator :: IO (J ('Iface "java.util.Iterator")) newIterator = do let tblPtr :: Int64 tblPtr = undefined iterator <- (loadJavaWrappers >> (((((((qqMarker (Proxy :: Proxy "{ return new java.util.Iterator() {\n @Override\n public native boolean hasNext();\n\n @Override\n public native Object next();\n\n @Override\n public void remove() {\n throw new UnsupportedOperationException();\n }\n\n private native v oid hsFinalize(long tblPtr);\n\n @Override\n public void finalize() {\n hsFinalize($tblPtr);\n }\n } ; }")) (Proxy :: Proxy "inline__method_0")) (Proxy :: Proxy "tblPtr")) (Proxy :: Proxy 106)) (tblPtr, ())) Proxy) (((callStatic (fromString "io.tweag.inlinejava.Inline__jvmstreaming022inplace_Language_Java_Streaming")) (fromString "inline__method_0")) [coerce tblPtr]))) undefined class Coercible (a :: Type) where type Ty a :: JType class Coercibles xs (tys :: k) | xs -> tys instance Coercibles () () instance (ty ~ Ty x, Coercible x, Coercibles xs tys) => Coercibles (x, xs) '(ty, tys) qqMarker :: forall -- k -- the kind variable shows up in Core (args_tys :: k) -- JType's of arguments tyres -- JType of result (input :: Symbol) -- input string of the quasiquoter (mname :: Symbol) -- name of the method to generate (antiqs :: Symbol) -- antiquoted variables as a comma-separated list (line :: Nat) -- line number of the quasiquotation args_tuple -- uncoerced argument types b. -- uncoerced result type (tyres ~ Ty b, Coercibles args_tuple args_tys, Coercible b, HasCallStack) => Proxy input -> Proxy mname -> Proxy antiqs -> Proxy line -> args_tuple -> Proxy args_tys -> IO b -> IO b qqMarker = undefined }}} With GHC 8.2.2, this is properly rejected by the typechecker: {{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:27:12: error: Variable not in scope: loadJavaWrappers :: IO a0 | 27 | (loadJavaWrappers >> | ^^^^^^^^^^^^^^^^ Bug.hs:36:16: error: Variable not in scope: callStatic :: t0 -> t1 -> [a2] -> IO a1 | 36 | (((callStatic | ^^^^^^^^^^ Bug.hs:40:17: error: Variable not in scope: coerce :: Int64 -> a2 | 40 | [coerce tblPtr]))) | ^^^^^^ }}} But in GHC 8.4.1-alpha2, this simply hangs forever. To make things more interesting, if you pass `-ddump-tc-trace` when compiling, you'll get a panic: {{{ $ /opt/ghc/8.4.1/bin/ghc Bug.hs -ddump-tc-trace ... kcLHsQTyVars: cusk JType [] [] [] [] * [] [] [] [] kcTyClGroup: initial kinds [rB8 :-> ATcTyCon JType :: *, rB9 :-> APromotionErr RecDataConPE] txExtendKindEnv [rB8 :-> ATcTyCon JType :: *, rB9 :-> APromotionErr RecDataConPE] kcTyClDecl { JType env2 [] tcExtendBinderStack [] env2 [] tcExtendBinderStack [] lk1 Symbol tcTyVar2a Symbol * u_tys tclvl 1 * ~ TYPE t_a1qq[tau:1] arising from a type equality * ~ TYPE t_a1qq[tau:1] u_tys tclvl 1 'GHC.Types.LiftedRep ~ t_a1qq[tau:1] arising from a type equality * ~ TYPE t_a1qq[tau:1] u_tys tclvl 1 GHC.Types.RuntimeRep ~ GHC.Types.RuntimeRep arising from a kind equality arising from t_a1qq[tau:1] ~ 'GHC.Types.LiftedRep u_tys yields no coercion writeMetaTyVar t_a1qq[tau:1] :: GHC.Types.RuntimeRep := 'GHC.Types.LiftedRep u_tys yields no coercion u_tys yields no coercion checkExpectedKind * TYPE t_a1qq[tau:1] <*>_N kcLHsQTyVars: not-cuskghc: panic! (the 'impossible' happened) (GHC version 8.4.0.20180118 for x86_64-unknown-linux): kcConDecl }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: Old description:
This issue prevents `jvm-streaming` from compiling with GHC 8.4.1-alpha2. Here is my best attempt at minimizing the issue:
{{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Bug () where
import Data.Kind (Type) import Data.Proxy (Proxy(..)) import Data.String (fromString) import Data.Int (Int64) import GHC.Stack (HasCallStack) import GHC.TypeLits (Nat, Symbol)
data JType = Iface Symbol
data J (a :: JType)
newIterator :: IO (J ('Iface "java.util.Iterator")) newIterator = do let tblPtr :: Int64 tblPtr = undefined iterator <- (loadJavaWrappers >> (((((((qqMarker (Proxy :: Proxy "{ return new java.util.Iterator() {\n @Override\n public native boolean hasNext();\n\n @Override\n public native Object next();\n\n @Override\n public void remove() {\n throw new UnsupportedOperationException();\n }\n\n private native v oid hsFinalize(long tblPtr);\n\n @Override\n public void finalize() {\n hsFinalize($tblPtr);\n }\n } ; }")) (Proxy :: Proxy "inline__method_0")) (Proxy :: Proxy "tblPtr")) (Proxy :: Proxy 106)) (tblPtr, ())) Proxy) (((callStatic (fromString "io.tweag.inlinejava.Inline__jvmstreaming022inplace_Language_Java_Streaming")) (fromString "inline__method_0")) [coerce tblPtr]))) undefined
class Coercible (a :: Type) where type Ty a :: JType
class Coercibles xs (tys :: k) | xs -> tys instance Coercibles () () instance (ty ~ Ty x, Coercible x, Coercibles xs tys) => Coercibles (x, xs) '(ty, tys)
qqMarker :: forall -- k -- the kind variable shows up in Core (args_tys :: k) -- JType's of arguments tyres -- JType of result (input :: Symbol) -- input string of the quasiquoter (mname :: Symbol) -- name of the method to generate (antiqs :: Symbol) -- antiquoted variables as a comma-separated list (line :: Nat) -- line number of the quasiquotation args_tuple -- uncoerced argument types b. -- uncoerced result type (tyres ~ Ty b, Coercibles args_tuple args_tys, Coercible b, HasCallStack) => Proxy input -> Proxy mname -> Proxy antiqs -> Proxy line -> args_tuple -> Proxy args_tys -> IO b -> IO b qqMarker = undefined }}}
With GHC 8.2.2, this is properly rejected by the typechecker:
{{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:27:12: error: Variable not in scope: loadJavaWrappers :: IO a0 | 27 | (loadJavaWrappers >> | ^^^^^^^^^^^^^^^^
Bug.hs:36:16: error: Variable not in scope: callStatic :: t0 -> t1 -> [a2] -> IO a1 | 36 | (((callStatic | ^^^^^^^^^^
Bug.hs:40:17: error: Variable not in scope: coerce :: Int64 -> a2 | 40 | [coerce tblPtr]))) | ^^^^^^ }}}
But in GHC 8.4.1-alpha2, this simply hangs forever.
To make things more interesting, if you pass `-ddump-tc-trace` when compiling, you'll get a panic:
{{{ $ /opt/ghc/8.4.1/bin/ghc Bug.hs -ddump-tc-trace ... kcLHsQTyVars: cusk JType [] [] [] [] * [] [] [] [] kcTyClGroup: initial kinds [rB8 :-> ATcTyCon JType :: *, rB9 :-> APromotionErr RecDataConPE] txExtendKindEnv [rB8 :-> ATcTyCon JType :: *, rB9 :-> APromotionErr RecDataConPE] kcTyClDecl { JType env2 [] tcExtendBinderStack [] env2 [] tcExtendBinderStack [] lk1 Symbol tcTyVar2a Symbol * u_tys tclvl 1 * ~ TYPE t_a1qq[tau:1] arising from a type equality * ~ TYPE t_a1qq[tau:1] u_tys tclvl 1 'GHC.Types.LiftedRep ~ t_a1qq[tau:1] arising from a type equality * ~ TYPE t_a1qq[tau:1] u_tys tclvl 1 GHC.Types.RuntimeRep ~ GHC.Types.RuntimeRep arising from a kind equality arising from t_a1qq[tau:1] ~ 'GHC.Types.LiftedRep u_tys yields no coercion writeMetaTyVar t_a1qq[tau:1] :: GHC.Types.RuntimeRep := 'GHC.Types.LiftedRep u_tys yields no coercion u_tys yields no coercion checkExpectedKind * TYPE t_a1qq[tau:1] <*>_N kcLHsQTyVars: not-cuskghc: panic! (the 'impossible' happened) (GHC version 8.4.0.20180118 for x86_64-unknown-linux): kcConDecl }}}
New description: This issue prevents `jvm-streaming` from compiling with GHC 8.4.1-alpha2. Here is my best attempt at minimizing the issue: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Bug () where import Data.Kind (Type) import Data.Proxy (Proxy(..)) import Data.String (fromString) import Data.Int (Int64) import GHC.Stack (HasCallStack) import GHC.TypeLits (Nat, Symbol) data JType = Iface Symbol data J (a :: JType) newIterator :: IO (J ('Iface "java.util.Iterator")) newIterator = do let tblPtr :: Int64 tblPtr = undefined iterator <- (loadJavaWrappers >> (((((((qqMarker (Proxy :: Proxy "{ return new java.util.Iterator() {\n @Override\n public native boolean hasNext();\n\n @Override\n public native Object next();\n\n @Override\n public void remove() {\n throw new UnsupportedOperationException();\n }\n\n private native void hsFinalize(long tblPtr);\n\n @Override\n public void finalize() {\n hsFinalize($tblPtr);\n }\n } ; }")) (Proxy :: Proxy "inline__method_0")) (Proxy :: Proxy "tblPtr")) (Proxy :: Proxy 106)) (tblPtr, ())) Proxy) (((callStatic (fromString "io.tweag.inlinejava.Inline__jvmstreaming022inplace_Language_Java_Streaming")) (fromString "inline__method_0")) [coerce tblPtr]))) undefined class Coercible (a :: Type) where type Ty a :: JType class Coercibles xs (tys :: k) | xs -> tys instance Coercibles () () instance (ty ~ Ty x, Coercible x, Coercibles xs tys) => Coercibles (x, xs) '(ty, tys) qqMarker :: forall -- k -- the kind variable shows up in Core (args_tys :: k) -- JType's of arguments tyres -- JType of result (input :: Symbol) -- input string of the quasiquoter (mname :: Symbol) -- name of the method to generate (antiqs :: Symbol) -- antiquoted variables as a comma-separated list (line :: Nat) -- line number of the quasiquotation args_tuple -- uncoerced argument types b. -- uncoerced result type (tyres ~ Ty b, Coercibles args_tuple args_tys, Coercible b, HasCallStack) => Proxy input -> Proxy mname -> Proxy antiqs -> Proxy line -> args_tuple -> Proxy args_tys -> IO b -> IO b qqMarker = undefined }}} With GHC 8.2.2, this is properly rejected by the typechecker: {{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:27:12: error: Variable not in scope: loadJavaWrappers :: IO a0 | 27 | (loadJavaWrappers >> | ^^^^^^^^^^^^^^^^ Bug.hs:36:16: error: Variable not in scope: callStatic :: t0 -> t1 -> [a2] -> IO a1 | 36 | (((callStatic | ^^^^^^^^^^ Bug.hs:40:17: error: Variable not in scope: coerce :: Int64 -> a2 | 40 | [coerce tblPtr]))) | ^^^^^^ }}} But in GHC 8.4.1-alpha2, this simply hangs forever. To make things more interesting, if you pass `-ddump-tc-trace` when compiling, you'll get a panic: {{{ $ /opt/ghc/8.4.1/bin/ghc Bug.hs -ddump-tc-trace ... kcLHsQTyVars: cusk JType [] [] [] [] * [] [] [] [] kcTyClGroup: initial kinds [rB8 :-> ATcTyCon JType :: *, rB9 :-> APromotionErr RecDataConPE] txExtendKindEnv [rB8 :-> ATcTyCon JType :: *, rB9 :-> APromotionErr RecDataConPE] kcTyClDecl { JType env2 [] tcExtendBinderStack [] env2 [] tcExtendBinderStack [] lk1 Symbol tcTyVar2a Symbol * u_tys tclvl 1 * ~ TYPE t_a1qq[tau:1] arising from a type equality * ~ TYPE t_a1qq[tau:1] u_tys tclvl 1 'GHC.Types.LiftedRep ~ t_a1qq[tau:1] arising from a type equality * ~ TYPE t_a1qq[tau:1] u_tys tclvl 1 GHC.Types.RuntimeRep ~ GHC.Types.RuntimeRep arising from a kind equality arising from t_a1qq[tau:1] ~ 'GHC.Types.LiftedRep u_tys yields no coercion writeMetaTyVar t_a1qq[tau:1] :: GHC.Types.RuntimeRep := 'GHC.Types.LiftedRep u_tys yields no coercion u_tys yields no coercion checkExpectedKind * TYPE t_a1qq[tau:1] <*>_N kcLHsQTyVars: not-cuskghc: panic! (the 'impossible' happened) (GHC version 8.4.0.20180118 for x86_64-unknown-linux): kcConDecl }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Wow! This regression was //also// triggered by commit 8e15e3d370e9c253ae0dbb330e25b72cb00cdb76 (`Improve error messages around kind mismatches.`), putting it in good company with #14038 and #14720. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: goldfire (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, perhaps we should consider reverting this commit for 8.4. It would be sad to do so, but it seems like it is causing quite some trouble. Thanks for pinpointing these, Ryan! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Here's a diagnosis. We have {{{ class Coercibles k k1 (xs :: k) (tys :: k1) | xs -> tys instance forall k (ty :: JType) x xs (tys :: k). (ty ~ Ty x, Coercible x, Coercibles * k xs tys) => Coercibles * (JType, k) (x, xs) '(ty, tys) }}} and a wanted constraint {{{ [WD] $dCoercibles_a2K3 :: Coercibles * (JType, k_a2My[tau:1]) (Int64, ()) args_tys_a2JU[tau:1] where args_tys_a2JU :: (JType, kappa1) }}} Now, from the fundep `xs -> tys` we generate {{{ [D] arg_tys_a2JU ~ (ty::JType, tys::kappa2) }}} where `ty`, `tys`, and `kappa2` are all ''fresh unification variables''. They are fresh because they they are not directly fixed by `(x,xs)` in the instance decl, but only indirectly via the context of the instance decl (so-called "liberal" fundeps). This is legitimate. But this new derived equality is hetero-kinded, so we "park" it (as a `CIrredCan`) and emit a derived equality on the kinds {{{ [D] (JType, kappa1) ~ (JType, kappa2) }}} We solve this, by `kappa1 := kappa2`. That kicks out the two inert, unsolved constraints, both of which mention `kappa1`: {{{ [WD] $dCoercibles_a2K3 :: Coercibles * (JType, k_a2My[tau:1]) (Int64, ()) args_tys_a2JU[tau:1] [D] arg_tys_a2JU ~ (ty::JType, tys::kappa2) }}} Alas, we choose the ''former'' to solve; and that simply repeats the entire process from the beginning. If instead we chose the derived equality constraint, the `kappa1 := kappa2` would make the equality homo-kinded, so we'd solve with `args_tys_a2JU := (ty,tys)`; and now the `Coercibles` constraint matches the instance and can be solved. And even if the `Coercibles` constraint doesn't (yet) match an instance, (maybe there's another parameter to the class that prevents the match) provided we've processed all the equalities coming from the fundeps first, we'll find that, if we generate fundeps again, they are all no-ops. Bottom line: one fix would be to prioritise equality constraints, even if they are Derived. Currently we priorities Wanted constraints in the work-list over Derived, on the grounds that if we solve all the Wanted constraints we may never need to process those Derived ones at all. Another (possibly better) approach might be to remember when we have generated fundeps from a class constraint, and refrain from doing so a second time. But that seems hard, because as we rewrite the class constraint we may learn more about some of its arguments, and therefore expose more possible fundeps. So it's hard to say when we "have generated the fundeps" from a class constraint. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.4.1-alpha1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: This is a bad bug, now fixed. Merge if poss. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: performance bug | polykinds/T14723 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => polykinds/T14723 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14723: GHC 8.4.1-alpha loops infinitely when typechecking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: performance bug | polykinds/T14723 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 77cdf60c8a68d2208cd8109d82b5f83b17bf0e91. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14723#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC