
#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