[GHC] #11608: Possible type-checker regression in GHC 8.0 when compiling `microlens`

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: (Type checker) | 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: -------------------------------------+------------------------------------- I just updated the GHC 8.0 snapshot I was using from 8.0.0.20160214-g977fb8 to 8.0.0.20160218-g23baff7, and suddenly hackage:microlens-0.4.2.0 fails to build with {{{ ... Preprocessing library microlens-0.4.2.0... [1 of 4] Compiling Lens.Micro.Type ( src/Lens/Micro/Type.hs, dist/build/Lens/Micro/Type.o ) [2 of 4] Compiling Lens.Micro.Internal ( src/Lens/Micro/Internal.hs, dist/build/Lens/Micro/Internal.o ) src/Lens/Micro/Internal.hs:184:3: error: • Couldn't match type ‘s’ with ‘g0 a’ ‘s’ is untouchable inside the constraints: (Traversable g, s ~ g a, t ~ g b, Applicative f) bound by the type signature for: each :: (Traversable g, s ~ g a, t ~ g b, Applicative f) => (a -> f b) -> s -> f t at src/Lens/Micro/Internal.hs:184:3-27 • In the ambiguity check for ‘each’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: each :: forall s t a b. Each s t a b => Traversal s t a b In the class declaration for ‘Each’ }}} ...is this a regression or a feature? :-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | 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 hvr): hackage:free-4.12.4 has a similiar sudden failure: {{{ Preprocessing library free-4.12.4... [ 1 of 16] Compiling Control.Monad.Free.TH ( src/Control/Monad/Free/TH.hs, dist/build/Control/Monad/Free/TH.o ) [ 2 of 16] Compiling Control.Monad.Free.Class ( src/Control/Monad/Free/Class.hs, dist/build/Control/Monad/Free/Class.o ) src/Control/Monad/Free/Class.hs:106:3: error: • Couldn't match type ‘m’ with ‘t0 n0’ ‘m’ is untouchable inside the constraints: (m ~ t n, MonadTrans t, MonadFree f n, Functor f) bound by the type signature for: wrap :: (m ~ t n, MonadTrans t, MonadFree f n, Functor f) => f (m a) -> m a at src/Control/Monad/Free/Class.hs:106:3-24 • In the ambiguity check for ‘wrap’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: wrap :: forall (f :: * -> *) (m :: * -> *). MonadFree f m => forall a. f (m a) -> m a In the class declaration for ‘MonadFree’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | 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 RyanGlScott): Specifically, the issue seems to pertain to type equalities in default signatures in typeclasses. Here is the failing code, reduced to reproducible examples: From [http://hackage.haskell.org/package/microlens-0.4.2.0/docs/src/Lens- Micro-Internal.html#line-184 microlens]: {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where each :: Traversal s t a b default each :: (Traversable g, s ~ g a, t ~ g b) => Traversal s t a b each = traverse }}} From [http://hackage.haskell.org/package/free-4.12.4/docs/src/Control- Monad-Free-Class.html#line-106 free]: {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} class MonadTrans t where lift :: Monad m => m a -> t m a class Monad m => MonadFree f m | m -> f where wrap :: f (m a) -> m a default wrap :: (m ~ t n, MonadTrans t, MonadFree f n, Functor f) => f (m a) -> m a wrap = join . lift . wrap . fmap return }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * failure: None/Unknown => GHC rejects valid program * version: => 8.0.1-rc2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Just to be clear, afaik this doesn't occur with 8.0.1-rc2, but rather with a more recent 8.0.01 snapshot (as described in the description). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hvr): * cc: goldfire (added) Comment: It seems like e1631b3b58b7440d3d5a8bf72f1490df635792fb may have been the culprit -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): I've temporarily reverted e1631b3b58b7440d3d5a8bf72f1490df635792fb in the `ghc-8.0` branch ''only'', via 881b6ccf5c1dbc09d1d16b1b4643e3dec9387047. I'm not reverting this in GHC HEAD yet, waiting for Richard to comment how we should proceed here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire Comment: I think there's an underlying problem here and that putting the fundep back in is not necessarily the right solution. Will need to look a bit deeper to really know. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Aha. In a class decl we use a `TyVar` (not a skolem `TcTyVar`) for the class variable(s). (There is a good reason for this: in the final `Class` value we don't want any `TcTyVar`s.) Then in `TcFlatten.flatten_tyvar` we see {{{ flatten_tyvar tv | not (isTcTyVar tv) -- Happens when flatten under a (forall a. ty) = flatten_tyvar3 tv }}} This case catches that class variable. In the ambiguity check for the type sig for `each` we have a Given equality for the class variable. Then, because of the above test we fail to take advantage of the Given. (And the error message too is misleading.) Solution: delete the above equation, so that we treat `TyVar` and skolem `TcTyVar` the same. I'm validating now. The `TyVar`/`TcTyVar` story is not great. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: goldfire => simonpj Comment: Actually there's a better way. Anyway I'm on this. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens`
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: simonpj
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler (Type | Version: 8.0.1-rc2
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): NB: the `isTcTyVar` could conceivably cause extra ASSERT failures when DEBUG is on. I didn't see any, but keep your eyes open. However, ignoring them (ie no `-DDEBUG`) is simply what happens today and is fine. So things will not be worse. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11608 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => typecheck/should_compile/T11608 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11608 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged as 7f15c2b8cd0b8c9f2e407b3a91a5541677df306b. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11608 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Hm. These `ASSERT`s used to be here, and I removed them because they were triggering on kind variables, which were not always `TcTyVar`s. However, if the `dependent` set of tests in the testsuite aren't failing here, then perhaps things improved from when I removed the `ASSERT`s. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11608 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It seems that way, but I did not do a full stage2 build with DEBUG on. Thomie may do that for us :-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11608 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Travis is reporting this at the moment: {{{ Unexpected failures: polykinds MonoidsTF [exit code non-0] (normal) polykinds T11480b [exit code non-0] (normal) polykinds T11523 [exit code non-0] (normal) th T3100 [exit code non-0] (normal) typecheck/should_compile T3692 [exit code non-0] (normal) typecheck/should_fail T3592 [stderr mismatch] (normal) typecheck/should_fail TcCoercibleFail [stderr mismatch] (normal) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11608 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Jolly good. * The `polykinds` ones are discussed in #11648 * `TcCoercibleFail` is really supposed to fail with `-DDEBUG` (exponential sized types) * I have a patch coming for the other three. So this is good news really. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens`
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: simonpj
Type: bug | Status: merge
Priority: highest | Milestone: 8.0.1
Component: Compiler (Type | Version: 8.0.1-rc2
checker) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | typecheck/should_compile/T11608
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by simonpj):
* status: closed => merge
Comment:
Here's the patch for the other three
{{{
commit 3c29c770be7a8c7268dcb8d8624853428aa42071
Author: Simon Peyton Jones

#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens` -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11608 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: comment:18 has been merged to `ghc-8.0` as 43163e3bd5bcd7c92fc692b365be750a7b766026. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11608#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC