[GHC] #11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope"

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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: -------------------------------------+------------------------------------- Consider {{{#!hs {-# OPTIONS_GHC -Wall #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StaticPointers #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableSuperClasses #-} module Bug where import Data.Kind import Data.Typeable import GHC.StaticPtr {------------------------------------------------------------------------------- Standard Cloud-Haskell-like infrastructure See https://ghc.haskell.org/trac/ghc/wiki/TypeableT for a dicussion of 'SC'. -------------------------------------------------------------------------------} class Serializable a -- empty class, just for demonstration purposes instance Serializable a => Serializable [a] data Static :: * -> * where StaticPtr :: StaticPtr a -> Static a StaticApp :: Static (a -> b) -> Static a -> Static b staticApp :: StaticPtr (a -> b) -> Static a -> Static b staticApp = StaticApp . StaticPtr data Dict :: Constraint -> * where Dict :: c => Dict c class c => SC c where dict :: Static (Dict c) instance (Typeable a, SC (Serializable a)) => SC (Serializable [a]) where dict = aux `staticApp` dict where aux :: StaticPtr (Dict (Serializable a) -> Dict (Serializable [a])) aux = static (\Dict -> Dict) {------------------------------------------------------------------------------- Demonstrate the bug -------------------------------------------------------------------------------} newtype MyList a = MyList [a] deriving instance (Typeable a, SC (Serializable a)) => SC (Serializable (MyList a)) }}} This gives the following type error: {{{ Bug1.hs:40:1: error: • Can't make a derived instance of ‘SC (Serializable (MyList a))’: The data constructors of ‘Serializable’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SC (Serializable a) => SC (Serializable (MyList a))’ }}} This of course doesn't make much sense: `Serializable` is a type class, not a datatype, and doesn't have data constructors. I wasn't sure if this deriving clause was going to work at all, or whether I would expect it to. Since `MyList` is a newtype wrapper around `[a]`, and we have the requisite instance {{{#!hs instance (Typeable a, SC (Serializable a)) => SC (Serializable [a]) }}} I was kind of hoping that `GeneralizedNewtypeDeriving` would work its magic. However, even if it cannot, the error message should probably change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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): Ha! Interesting. The error message embodies the assumption that in {{{ instance .. => C (T a b c) }}} that `T` is an algebraic data type; but here is is a class. So a question arises: * Does GND work for classes? Well, does this work? {{{ instance (Typeable a, SC (Serializable a)) => SC (Serializable (MyList a)) where dict = coerce (dict :: Static (Dict (Serializable [a]))) }}} If we got past the test, I think that's what we'd generate. I suspect you'll get a similar error from the `corece`, but try it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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 edsko): After adding the required role annotation to `Serializable`, this works: {{{#!hs instance (Typeable a, SC (Serializable a)) => SC (Serializable (MyList a)) where dict = coerce (dict :: Static (Dict (Serializable [a]))) }}} but the standalone deriving clause still gives the same error as reported above. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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 edsko): Incidentally, when `Serializable` has a nominal role, that call to `coerce` is rejected by ghc 8.0 with {{{ Bug.hs:70:10: error: • Couldn't match type ‘[a]’ with ‘MyList a’ arising from a use of ‘coerce’ • In the expression: coerce (dict :: Static (Dict (Serializable [a]))) In an equation for ‘dict’: dict = coerce (dict :: Static (Dict (Serializable [a]))) In the instance declaration for ‘SC (Serializable (MyList a))’ • Relevant bindings include dict :: Static (Dict (Serializable (MyList a))) (bound at Bug.hs:70:3) }}} which I found somewhat confusing; "Couldn't match type `[a]` with `MyList a` arising from a use of `coerce`" isn't very obvious; ghc 7.10.3 here is much much clearer: {{{ Bug.hs:70:10: Couldn't match type ‘MyList a’ with ‘[a]’ arising from trying to show that the representations of ‘Static (Dict (Serializable [a]))’ and ‘Static (Dict (Serializable (MyList a)))’ are the same Relevant role signatures: type role [] representational type role MyList representational type role Dict representational type role Static representational type role Serializable nominal Relevant bindings include dict :: Static (Dict (Serializable (MyList a))) (bound at Bug.hs:70:3) In the expression: coerce (dict :: Static (Dict (Serializable [a]))) In an equation for ‘dict’: dict = coerce (dict :: Static (Dict (Serializable [a]))) In the instance declaration for ‘SC (Serializable (MyList a))’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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 edsko): * Attachment "Bug11509.hs" added. Test case with some CPP to make it work with 7.10 and 8.0 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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): As Simon says, GHC's various `deriving` bits rely heavily on the assumption that the outermost type constructor is that of a datatype. I honestly have no idea how you'd make this work for typeclasses, especially since in your example, GHC would need some way to "tunnel down" into a type and figure out what the newtype is (if there even is one!). Throw in things like `MultiParamTypeClasses` and type synonyms, and I imagine that this would get extremely hairy. Would you be happy with a different error message to the tune of: {{{ Bug1.hs:40:1: error: • Can't make a derived instance of ‘SC (Serializable (MyList a))’: Cannot derive an instance of the form ‘C (T a b c)‘ where ‘T‘ is a type class • In the stand-alone deriving instance for ‘SC (Serializable a) => SC (Serializable (MyList a))’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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 edsko): Yes, that would at least be a much clearer error message. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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): * owner: => RyanGlScott Comment: After #10598, GHC has been refactored to propagate information about which deriving mechanism was chosen further into the compiler, so fixing this issue properly (i.e., erroring on stock or newtype deriving, but not on anyclass deriving) is much easier now. I'll take this one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2558 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2558 Comment: At least, I thought deriving strategies would come into play, but it turns out a different check already present in GHC gives a pretty reasonable error message for this scenario already. So now the code above gives the error message: {{{ • Can't make a derived instance of ‘SC (Serializable (MyList a))’: ‘SC’ is not a stock derivable class (Eq, Show, etc.) Try enabling DeriveAnyClass • In the stand-alone deriving instance for ‘(Typeable a, SC (Serializable a)) => SC (Serializable (MyList a))’ }}} `DeriveAnyClass` technically can't be used derive instances of kind `a -> Constraint` right now, but they will be able to once #12144 is fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of
<typeclass> are not all in scope"
-------------------------------------+-------------------------------------
Reporter: edsko | Owner: RyanGlScott
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2558
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2558 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Unless others would prefer we merge this I think I will let this one slide until 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2558 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => new * owner: RyanGlScott => * resolution: fixed => Comment: Ack! I apologize Ben, I accidentally linked to the wrong Trac ticket number from the Diff description. Phab:D2557 was meant for #12512, not this one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2558 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of
<typeclass> are not all in scope"
-------------------------------------+-------------------------------------
Reporter: edsko | Owner:
Type: bug | Status: patch
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2558
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2558 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: This would be quite an effort to backport and the issue seems non- critical. Let's punt this to 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11509: Incorrect error message in StandaloneDeriving: "The data constructors of <typeclass> are not all in scope" -------------------------------------+------------------------------------- Reporter: edsko | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2558 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11509#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC