[GHC] #10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8)

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Type checker) | 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): | -------------------------------------+------------------------------------- Distilled example is the following: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE AllowAmbiguousTypes #-} -- not needed for 7.8, should not be needed for 7.10 as well {-# OPTIONS_GHC -Wall #-} module L () where import Prelude () -- clean up data IdT f a = IdC (f a) class ( m ~ Outer m (Inner m) ) => BugC (m :: * -> *) where type Inner m :: * -> * type Outer m :: (* -> *) -> * -> * bug :: ( forall n. ( n ~ Outer n (Inner n) , Outer n ~ Outer m ) => Inner n a) -> m a instance BugC (IdT m) where type Inner (IdT m) = m type Outer (IdT m) = IdT bug f = IdC f }}} ghc-7.8 compiles the sample just fine: {{{ $ ghci a.hs GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling L ( a.hs, interpreted ) Ok, modules loaded: L. *L> :t bug bug :: (BugC (t1 t), Outer (t1 t) ~ t1, Inner (t1 t) ~ t) => (forall (n :: * -> *). (n ~ Outer n (Inner n), Outer n ~ Outer (t1 t)) => Inner n a) -> t1 t a }}} ghc-7.10 can't build it even with AllowAmbiguousTypes {{{ $ ghci a.hs GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling L ( a.hs, interpreted ) a.hs:28:17: Couldn't match type ‘m’ with ‘Inner (IdT m)’ ‘m’ is a rigid type variable bound by the instance declaration at a.hs:24:10 Expected type: Outer (IdT m) (Inner (IdT m)) Actual type: IdT m Relevant bindings include f :: forall (n :: * -> *). (n ~ Outer n (Inner n), Outer n ~ Outer (IdT m)) => Inner n a (bound at a.hs:28:9) bug :: (forall (n :: * -> *). (n ~ Outer n (Inner n), Outer n ~ Outer (IdT m)) => Inner n a) -> IdT m a (bound at a.hs:28:5) In the first argument of ‘IdC’, namely ‘f’ In the expression: IdC f In an equation for ‘bug’: bug f = IdC f Failed, modules loaded: none. }}} Without AllowAmbiguousTypes the error gives a hint on ambiguity (which does not really exist as I understand associated type families): {{{ $ ghci a-no-ambig-language.hs GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling L ( a.hs, interpreted ) a.hs:28:17: Couldn't match type ‘m’ with ‘Inner (IdT m)’ ‘m’ is a rigid type variable bound by the instance declaration at a.hs:24:10 Expected type: Outer (IdT m) (Inner (IdT m)) Actual type: IdT m Relevant bindings include f :: forall (n :: * -> *). (n ~ Outer n (Inner n), Outer n ~ Outer (IdT m)) => Inner n a (bound at a.hs:28:9) bug :: (forall (n :: * -> *). (n ~ Outer n (Inner n), Outer n ~ Outer (IdT m)) => Inner n a) -> IdT m a (bound at a.hs:28:5) In the first argument of ‘IdC’, namely ‘f’ In the expression: IdC f In an equation for ‘bug’: bug f = IdC f Failed, modules loaded: none. }}} It seems that ghc-7.8 is more correct here. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 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): -------------------------------------+------------------------------------- Comment (by thomie): Works fine with HEAD (ghc-7.11.20150921), also without `AllowAmbiguousTypes`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 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): -------------------------------------+------------------------------------- Comment (by slyfox): Oh that's good! ghc-7.10 branch doesn't work though. I wonder when it was fixed. {{{ $ inplace/bin/ghc-stage2 --interactive T10931.hs GHCi, version 7.10.2.20151003: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling L ( T10931.hs, interpreted ) T10931.hs:28:17: Couldn't match type ‘m’ with ‘Inner (IdT m)’ ‘m’ is a rigid type variable bound by the instance declaration at T10931.hs:24:10 Expected type: Outer (IdT m) (Inner (IdT m)) Actual type: IdT m Relevant bindings include f :: forall (n :: * -> *). (n ~ Outer n (Inner n), Outer n ~ Outer (IdT m)) => Inner n a (bound at T10931.hs:28:9) bug :: (forall (n :: * -> *). (n ~ Outer n (Inner n), Outer n ~ Outer (IdT m)) => Inner n a) -> IdT m a (bound at T10931.hs:28:5) In the first argument of ‘IdC’, namely ‘f’ In the expression: IdC f In an equation for ‘bug’: bug f = IdC f Failed, modules loaded: none. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 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): -------------------------------------+------------------------------------- Changes (by simonpj): * cc: goldfire (added) Comment: Thanks for a small test case. I've added a test so if this goes wrong again we'll know. I have not investigated in detail. Would someone like to git-bisect to find when it got fixed? I have a horrid feeling that it'll just be part of some fairly substantial change to the type constraint solver, which we won't want to merge en-masse to 7.10.3. As things stand, it's a bug in 7.10 that we don't know how to fix. I'm sure we could find out, but it'd take precious cycles. How bad is it if this library doesn't work? I imagine this is relatively rare else it'd show up more often. Richard; you might be interested. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 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): -------------------------------------+------------------------------------- Comment (by goldfire): This seems to have many of the same elements to #10009, which indeed cannot be merged. Are there known workarounds to #10009? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 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): -------------------------------------+------------------------------------- Comment (by slyfox): Replying to [comment:3 simonpj]:
How bad is it if this library doesn't work? I imagine this is relatively rare else it'd show up more often.
Nonworking library in 7.10 is absolutely not a problem for me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from
ghc-7.8)
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.2
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):
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: indexed- valid program | types/should_compile/T10931 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => indexed-types/should_compile/T10931 * milestone: => 8.0.1 Comment: Replying to [comment:4 goldfire]:
This seems to have many of the same elements to #10009, which indeed cannot be merged.
Replying to [comment:5 slyfox]:
Nonworking library in 7.10 is absolutely not a problem for me.
Let's close this one then, it is fixed in HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10931: layers-0.1 does not compile with ghc-7.10 (likely a regression from ghc-7.8) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: indexed- valid program | types/should_compile/T10931 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10931#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC