[GHC] #13601: GHC errors but hangs

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeFamilies, DataKinds, TypeInType #-} import GHC.Exts import Prelude (Bool(True,False),Integer,Ordering,undefined) import qualified Prelude import Data.Kind -------------------- -- class hierarchy type family Rep (rep :: RuntimeRep) :: RuntimeRep where -- Rep IntRep = IntRep -- Rep DoubleRep = IntRep -- Rep PtrRepUnlifted = IntRep -- Rep PtrRepLifted = PtrRepLifted class Boolean (Logic a) => Eq (a :: TYPE rep) where type Logic (a :: TYPE rep) :: TYPE (Rep rep) (==) :: a -> a -> Logic a class Eq a => POrd (a :: TYPE rep) where inf :: a -> a -> a class POrd a => MinBound (a :: TYPE rep) where minBound :: () -> a class POrd a => Lattice (a :: TYPE rep) where sup :: a -> a -> a class (Lattice a, MinBound a) => Bounded (a :: TYPE rep) where maxBound :: () -> a class Bounded a => Complemented (a :: TYPE rep) where not :: a -> a class Bounded a => Heyting (a :: TYPE rep) where infixr 3 ==> (==>) :: a -> a -> a class (Complemented a, Heyting a) => Boolean a (||) :: Boolean a => a -> a -> a (||) = sup (&&) :: Boolean a => a -> a -> a (&&) = inf }}} hangs with {{{ $ ghci a.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( a.hs, interpreted ) a.hs:18:16: error: C-c C-cInterrupted. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I was running out the door when I submitted that, here is a more minimal example {{{#!hs {-# Language TypeFamilies, DataKinds, TypeInType #-} -- {-# Language FlexibleContexts, UndecidableSuperClasses #-} import GHC.Exts -- (TYPE, RuntimeRep) import Data.Kind type family Rep (rep :: RuntimeRep) :: RuntimeRep class Boolean (Logic a) => Eq' (a :: TYPE rep) where type Logic (a :: TYPE rep) :: TYPE (Rep rep) class Eq' a => MinBound (a :: TYPE rep) where class Eq' a => Lattice (a :: TYPE rep) where class (MinBound a, Lattice a) => Boolean a }}} It is fixed by uncommenting the final two pragmas and writing {{{#!hs class (MinBound a, Lattice a) => Boolean (a :: TYPE rep) }}} ---- Alternatively, only commenting out `import GHC.Exts (TYPE, RuntimeRep)` gives us an ever-so-slightly different error {{{ c.hs:10:16: error: • Expected kind }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * keywords: => TypeInType, LevityPolymorphism -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I know roughly what is happening here. * When checking kinds we call `solveEqualities` which immediately reports type errors * The offending kind-equality constraint in this case has a `TypeEqOrigin` whose `uo_thing` is built by `checkExpectedKind`. * That `uo_thing` is printed as part of the error message. Alas it contains a type (not a kind); and that type involves some knot-tied `TyCons`. Result: black hole. The exact details are still hazy to me. The entire `uo_thing` stuff seems pretty grim. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I wondered about deferring the errors in `solveEqualities` by re-emitting them. Just jotting it down here; entirely untested. {{{ +{- + ; emitConstraints final_wc + ; traceTc "End solveEqualities }" (ppr final_wc) + ; when (anyErrorsWC final_wc) failM + ; return result } +-} @@ -145,0 +153,8 @@ solveEqualities thing_inside +anyErrorsWC :: WantedConstraints -> Bool +anyErrorsWC (WC { wc_simple = wanteds, wc_insol = insols, wc_impl = implics }) + = anyBag is_err wanteds + || anyBag is_err insols + || anyBag (anyErrorsWC . ic_wanted) implics + where + is_err ct = trulyInsoluble ct + }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): The `uo_thing` field was introduced in order to keep error messages reasonably stable during the `TypeInType` merge. Pre-`TypeInType`, kind errors reported what type had the kind that was involved in the error, and I wanted to keep this functionality post-`TypeInType`. That's the only reason the field exists. It was (and is) my hope to use `uo_thing` also for term-level error messages, as I think we can improve these through its use. One of the grim aspects of `uo_thing` is that `unifyType`'s type starts with `Outputable a => Maybe a -> ...` in order to use (possibly) something as the thing in the `uo_thing` field. But passing `Nothing` to `unifyType` causes ambiguity errors, because we can't know what `a` should be. So I have `noThing :: Maybe (HsExpr Name); noThing = Nothing` to resolve the ambiguity. I've been meaning to clean this up. Another missed opportunity after `TypeInType` is to use `TcTyCon` more fully. Type-checking can produce `TcTyCon`s instead of `TyCon`s, with the latter rewriting to the former only during the final zonk. This would mean that the type-checking knot needs to cover only zonking, instead of type- checking. That would surely fix this bug. In more direct response to comment:4, I'm dubious. If `solveEqualities` fails, then there is something ill-kinded lurking about, and I'm worried that some `failIfErrsM` and such won't fire, causing chaos. It may be possible to rein in the chaos, but I don't think it will be an easy win. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This appears to be fixed in GHC HEAD. I need to figure out which commit did the deed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13819 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13819 Comment: This was fixed in c2417b87ff59c92fbfa8eceeff2a0d6152b11a47 (Fix #13819 by refactoring TypeEqOrigin.uo_thing). TODO: Add a regression test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13819 | Differential Rev(s): Phab:D3794 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3794 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13601: GHC errors but hangs
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: TypeInType,
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #13819 | Differential Rev(s): Phab:D3794
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#13601: GHC errors but hangs -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_fail/T13601 Blocked By: | Blocking: Related Tickets: #13819 | Differential Rev(s): Phab:D3794 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => dependent/should_fail/T13601 * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13601#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC