[GHC] #14605: Core Lint error

#14605: Core Lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: TypeInType, | Operating System: Unknown/Multiple DeferredTypeErrors | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This piece of code fails when run with `ghci -ignore-dot-ghci -fdefer- type-errors -dcore-lint bug.hs`, maybe same as my previous #14584. {{{#!hs {-# Language DerivingStrategies #-} {-# Language GeneralizedNewtypeDeriving #-} {-# Language InstanceSigs #-} {-# Language KindSignatures #-} {-# Language PolyKinds #-} {-# Language ScopedTypeVariables #-} {-# Language TypeApplications #-} {-# Language TypeFamilies #-} {-# Language TypeInType #-} {-# Language TypeOperators #-} {-# Language UndecidableInstances #-} import Data.Kind import Data.Functor.Identity import Data.Functor.Product type a <-> b = a -> b -> Type class Iso (iso :: a <-> b) where iso :: a -> b osi :: b -> a data Iso_Bool :: Either () () <-> Bool instance Iso Iso_Bool where class Representable f where type Rep f :: Type index :: f a -> (Rep f -> a) tabulate :: (Rep f -> a) -> f a class Comonad w where extract :: w a -> a duplicate :: w a -> w (w a) newtype Co f a = Co (f a) deriving newtype (Functor, Representable) instance (Representable f, Monoid (Rep f)) => Comonad (Co f) where extract = (`index` mempty) newtype WRAP (iso::old <-> new) f a = WRAP (f a) instance (Representable f, Rep f ~ old, Iso iso) => Representable (WRAP (iso :: old <-> new) f) where type Rep (WRAP (iso :: old <-> new) f) = new index :: WRAP iso f a -> (new -> a) index (WRAP fa) = index fa . osi @old @new @iso tabulate :: (new -> a) -> WRAP iso f a tabulate gen = WRAP $ tabulate (gen . iso @old @new @iso) newtype PAIR a = PAIR (Co (WRAP Iso_Bool (Product Identity Identity)) a) deriving newtype Comonad }}} I unfortunately don't have time to find a more minimal example. Core linter vomits a lot of errors on 8.2.1 & 8.3.20171208. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14605 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14605: Core Lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: TypeInType, | DeferredTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14584 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * related: => #14584 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14605#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14605: Core Lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: TypeInType, | DeferredTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14584 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): Similar to #14584. The essence is the code that is generated via GND for `Comonad PAIR`, which I've reduced to: {{{ {-# Language TypeApplications #-} {-# Language ImpredicativeTypes #-} import GHC.Prim (coerce) duplicate = coerce @(forall x. ()) @(forall x. x) }}} (though it's possible there are more factors causing the bug and I isolated only one of them) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14605#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14605: Core Lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: TypeInType, | DeferredTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14584 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The error is a kind error under a forall type, which gets an implication constraint, but with nowhere to put its (value) bindings. The the deferred type error produces a value binding that is then discarded. Monoidal, you are brilliant at reducing these examples to their essence. Amazing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14605#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14605: Core Lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: TypeInType, | DeferredTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14584 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Thanks monoidal for cleaning up my mess :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14605#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14605: Core Lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: TypeInType, | DeferredTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14584 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Richard and I decided that the simple way to do this is to switch off deferred type errors when inside a forall-unification. One could also imagine using the enclosing value bindings, but the necessary variables won't be in scope there. We could instead bind a bogus coercion in the outside scope, with a vanilla type like `() ~ ()` and then unsafe-corece it to the one we need. But it's more complicated and doesn't seem with the pain unless we get user pressure. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14605#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14605: Core Lint error
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Resolution: | Keywords: TypeInType,
| DeferredTypeErrors
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #14584 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14605: Core Lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: TypeInType, | DeferredTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T14605 Blocked By: | Blocking: Related Tickets: #14584 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_fail/T14605 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14605#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC