[GHC] #16323: Cannot deduce X error with X provided

#16323: Cannot deduce X error with X provided ----------------------------------------+--------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Windows Architecture: Unknown/Multiple | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+--------------------------------- The following code {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} module TorXakis.Test ( -- * Referable Referable(..) ) where import Data.Hashable import qualified Data.HashMap as HashMap -- | A referable class class Referable a where type Ref a toRef :: a -> Ref a -- | Map of Referable objects. data (Referable a, Ord (Ref a), Hashable (Ref a)) => RefMap a = RefMap { -- | the HashMap toHashMap :: HashMap.Map (Ref a) a } deriving (Eq, Ord, Show, Read) }}} gives the following errors {{{ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:43: error: * Could not deduce (Ord (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: (Eq a, Referable a) bound by the deriving clause for `Eq (RefMap a)' at src\TorXakis\Test.hs:20:43-44 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Eq (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:47: error: * Could not deduce (Hashable (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: (Ord a, Referable a) bound by the deriving clause for `Ord (RefMap a)' at src\TorXakis\Test.hs:20:47-49 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Ord (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^^ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:52: error: * Could not deduce (Ord (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: (Show a, Referable a) bound by the deriving clause for `Show (RefMap a)' at src\TorXakis\Test.hs:20:52-55 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Show (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^^^ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:58: error: * Could not deduce (Ord (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: (Read a, Referable a) bound by the deriving clause for `Read (RefMap a)' at src\TorXakis\Test.hs:20:58-61 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Read (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^^^ -- While building package txs-basics-0.1.0.0 using: C:\sr\setup-exe-cache\x86_64-windows-integersimple\Cabal- simple_Z6RU0evB_2.0.1.0_ghc-8.2.2.exe --builddir=.stack-w ork\dist\67675594 build lib:txs-basics --ghc-options " -ddump-hi -ddump- to-file" Process exited with code: ExitFailure 1 }}} yet the requirements such as {{{Ord (Ref a)}}} are clearly given to the data definition! possibly related to #16319 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16323 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16323: Cannot deduce X error with X provided in TypeFamilies ---------------------------------+---------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16323#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16323: Cannot deduce X error with X provided in TypeFamilies ---------------------------------+---------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Deriving Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by simonpj): * keywords: => Deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16323#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16323: Cannot deduce X error with X provided in TypeFamilies ---------------------------------+---------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Deriving Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by pjljvdlaar): replacing data by newtype give slightly different errors {{{Eq (Ref a)}}} is also required. Adding this to the definition, i.e. {{{#!hs newtype (Referable a, Eq (Ref a), Ord (Ref a), Hashable (Ref a)) => RefMap a = RefMap { -- | the HashMap toHashMap :: HashMap.Map (Ref a) a } deriving (Eq, Ord, Show, Read) }}} still give the same errors for newtype (yet different from data): {{{ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:43: error: * Could not deduce (Eq (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: Eq a bound by the deriving clause for `Eq (RefMap a)' at src\TorXakis\Test.hs:20:43-44 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Eq (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:47: error: * Could not deduce (Ord (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: Ord a bound by the deriving clause for `Ord (RefMap a)' at src\TorXakis\Test.hs:20:47-49 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Ord (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^^ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:52: error: * Could not deduce (Ord (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: (Show a, Referable a) bound by the deriving clause for `Show (RefMap a)' at src\TorXakis\Test.hs:20:52-55 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Show (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^^^ C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:58: error: * Could not deduce (Ord (Ref a)) arising from the 'deriving' clause of a data type declaration from the context: (Read a, Referable a) bound by the deriving clause for `Read (RefMap a)' at src\TorXakis\Test.hs:20:58-61 Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself * When deriving the instance for (Read (RefMap a)) | 20 | } deriving (Eq, Ord, Show, Read) | ^^^^ -- While building package txs-basics-0.1.0.0 using: C:\sr\setup-exe-cache\x86_64-windows-integersimple\Cabal- simple_Z6RU0evB_2.0.1.0_ghc-8.2.2.exe --builddir=.stack-w ork\dist\67675594 build lib:txs-basics --ghc-options " -ddump-hi -ddump- to-file" Process exited with code: ExitFailure 1 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16323#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

The Haskell Report is vague about exactly when a deriving clause is legal. For example:
{{{#!hs data T0 f a = MkT0 a deriving( Eq ) data T1 f a = MkT1 (f a) deriving( Eq ) data T2 f a = MkT2 (f (f a)) deriving( Eq ) }}}
The natural generated Eq code would result in these instance declarations:
{{{#!hs instance Eq a => Eq (T0 f a) where ... instance Eq (f a) => Eq (T1 f a) where ... instance Eq (f (f a)) => Eq (T2 f a) where ... }}}
The first of these is obviously fine. The second is still fine, although less obviously. The third is not Haskell 98, and risks losing termination of instances.
GHC takes a conservative position: it accepts the first two, but not the
#16323: Cannot deduce X error with X provided in TypeFamilies -------------------------------------+------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: duplicate | Keywords: Deriving Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11008, #15868 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #11008, #15868 Comment: This is by design. Per the [https://downloads.haskell.org/~ghc/8.6.3/docs/html/users_guide/glasgow_exts.... #inferred-context-for-deriving-clauses users' guide section] on `deriving`: third. The rule is this: each constraint in the inferred instance context must consist only of type variables, with no repetitions.
This rule is applied regardless of flags. If you want a more exotic
context, you can write it yourself, using the standalone deriving mechanism. A similar situation is happening in the code that you are trying to derive. For instance, this: {{{#!hs data RefMap a = RefMap (Map (Ref a) a) deriving Eq }}} Would require generating the following code: {{{#!hs instance (Eq a, Eq (Ref a)) => Eq (RefMap a) where ... }}} The constraint `Eq (Ref a)` has an occurrence of `Ref` underneath the class `Eq`, which isn't a type variable. Therefore, GHC conservatively backs out and refuses to infer it. In order to write this, GHC requires that you use `StandaloneDeriving`, like so: {{{#!hs deriving instance (Eq a, Eq (Ref a)) => Eq (RefMap a) }}} #11008 and #15868 are about this same issue, so I'll close this ticket as a duplicate. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16323#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC