[GHC] #13998: Default Signature messes up arity of type constructor

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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: -------------------------------------+------------------------------------- I have a situation that's shown up in my `quantification` library that I believe is an issue with GHC's typeclass method defaulting mechanism. Here is a self-contained example: {{{ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} import Data.Type.Equality class EqForall f where eqForall :: f a -> f a -> Bool class EqForall f => EqForallPoly f where eqForallPoly :: f a -> f b -> Bool default eqForallPoly :: TestEquality f => f a -> f b -> Bool eqForallPoly = defaultEqForallPoly defaultEqForallPoly :: (TestEquality f, EqForall f) => f a -> f b -> Bool defaultEqForallPoly x y = case testEquality x y of Nothing -> False Just Refl -> eqForall x y data Atom = AtomInt | AtomString | AtomBool data Value (a :: Atom) where ValueInt :: Int -> Value 'AtomInt ValueString :: String -> Value 'AtomString ValueBool :: Bool -> Value 'AtomBool instance TestEquality Value where testEquality (ValueInt _) (ValueInt _) = Just Refl testEquality (ValueString _) (ValueString _) = Just Refl testEquality (ValueBool _) (ValueBool _) = Just Refl testEquality _ _ = Nothing instance EqForall Value where eqForall (ValueInt a) (ValueInt b) = a == b eqForall (ValueString a) (ValueString b) = a == b eqForall (ValueBool a) (ValueBool b) = a == b instance EqForallPoly Value main :: IO () main = putStrLn "done" }}} This fails to compile both with GHC 8.0 and with GHC 8.2rc3. The error reads: {{{ default_sig_limitation.hs:40:10: error: • Expecting one more argument to ‘Value’ Expected a type, but ‘Value’ has kind ‘Atom -> *’ • In the type ‘Value’ In the expression: Main.$dmeqForallPoly @Value In an equation for ‘eqForallPoly’: eqForallPoly = Main.$dmeqForallPoly @Value }}} If I replace `EqForallPoly` instance with something more explicit, it will compile just fine: {{{ instance EqForallPoly Value where eqForallPoly = defaultEqForallPoly }}} Fortunately, this workaround isn't bad at all. I don't really mind it, but I thought I'd bring it up here in case it bites someone else in the future. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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): Hm, seems to work for 7.8.4/8.0.1 on my end -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) Comment: It works on GHC 8.0.1 and earlier, but not on 8.0.2 or later. This can be explained by the fact that the way GHC typechecks default implementations received a drastic overhaul in 8.0.2. Unfortunately, that's been the root of many bugs... That being said, I have a hunch what is going on here. From inspecting the `-ddump-tc-trace` output, one can observe that GHC gives the following type signature for `$dmeqForallPoly`: {{{ tcInferId Main.$dmeqForallPoly :: forall k (f :: k -> *). EqForallPoly f => forall (a :: k) (b :: k). TestEquality f => f a -> f b -> Bool }}} Notice that the `k` comes //before// `f`. However, in the generated `EqForallPoly Value` instance (which can be seen with `-ddump-deriv`): {{{ Main.EqForallPoly [Main.Atom, Main.Value] Main.eqForallPoly = Main.$dmeqForallPoly @(Main.Value) }}} It's using `TypeApplications` to instantiate `k` to `Value`. This is wrong, however, since we really want to be instantiating //`f`// to `Value`. That is, we'd rather generate this code: {{{ instance EqForallPoly Value where eqForallPoly = $dmeqForallPoly @Atom @Value }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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 RyanGlScott): Just as well, perhaps the `k` in `$dmeqForallPoly` shouldn't be available for visible type application in the first place. Indeed, the code which generates `Main.$dmeqForallPoly @(Main.Value)` already [http://git.haskell.org/ghc.git/blob/d7b17517e26007f537feab490509c0e13e0e239a... filters out] invisible type arguments, but it seems that the `k` in `$dmeqForallPoly` isn't properly marked as invisible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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 RyanGlScott): I'm 99% sure the culprit is [http://git.haskell.org/ghc.git/blob/d7b17517e26007f537feab490509c0e13e0e239a... here]: {{{#!hs mkDefaultMethodType :: Class -> Id -> DefMethSpec Type -> Type -- Returns the top-level type of the default method mkDefaultMethodType _ sel_id VanillaDM = idType sel_id mkDefaultMethodType cls _ (GenericDM dm_ty) = mkSpecSigmaTy cls_tvs [pred] dm_ty where cls_tvs = classTyVars cls pred = mkClassPred cls (mkTyVarTys cls_tvs) }}} The second case (`GenericDM`) is what constructs the type of `$dmeqForallPoly`. Notice that it's using `mkSpecSigmaTy` to prepend the `forall k (f :: k -> *). EqForallPoly f => ...` bit to the rest of the type. However, because it's using `mkSpecSigmaTy`, every class tyvar binder has a visibility of `Specified`, meaning they'll all be available for visible type application, which isn't what we want. However, I'm not sure how to inform GHC that `k` should be invisible, but `f` should be visible, in this code. The problem is that the `Class` data type [http://git.haskell.org/ghc.git/blob/d7b17517e26007f537feab490509c0e13e0e239a... doesn't store any visibility information for its type variables]... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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 simonpj): Yes: the visiblity of the `k` type parameter for `$dmeqForAllPoly` is somehow inconsistent with that of the class. See `Note [TyBinders and ArgFlags]` in `TyCoRep`. I have a fix in progress. As usual you have nailed the right place. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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 RyanGlScott): Woo, Simon to the rescue! Out of curiosity, are you trying to fix this by changing the visibility of `k`, or changing the codegen to spit out `$dmeqForallPoly @Atom @Value` instead? The former fix sounds more principled, but I think harder, since it seems that GHC doesn't track visibility for class tyvars like I would have imagined: {{{ λ> :type +v eqForallPoly eqForallPoly :: forall k (f :: k -> *). EqForallPoly f => forall (a :: k) (b :: k). f a -> f b -> Bool }}} I would have expected instead: {{{ λ> :type +v eqForallPoly eqForallPoly :: forall {k} (f :: k -> *). EqForallPoly f => forall (a :: k) (b :: k). f a -> f b -> Bool }}} But this should probably go in a separate ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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 simonpj):
The problem is that the Class data type....
But the `classTyCon` has everything. The `classTyVars` are redundant, just there for convenience. I'm fixing it by using the visiblity of the class (tycon) parameters and using that consistently. `mkSpecSigmaTy` is deeply suspect. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | 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 RyanGlScott): Replying to [comment:7 simonpj]:
But the `classTyCon` has everything. The `classTyVars` are redundant, just there for convenience.
Oops, I overlooked that. Also, please ignore the noise in the latter part of comment:6 - the type signature wasn't pretty-printing the way I expected because I neglected to enable `-fprint-explicit-foralls`. If you do, you'll get: {{{ λ> :set -fprint-explicit-foralls λ> :type +v eqForallPoly eqForallPoly :: forall {k} (f :: k -> *). EqForallPoly f => forall (a :: k) (b :: k). f a -> f b -> Bool }}} as expected. So that is working as expected. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13998: Default Signature messes up arity of type constructor
-------------------------------------+-------------------------------------
Reporter: andrewthad | 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 Simon Peyton Jones

#13998: Default Signature messes up arity of type constructor -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T13998 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => deriving/should_compile/T13998 * resolution: => fixed Comment: OK, done! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13998#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC