[GHC] #14462: deriving on associated data types fails to find constraints

#14462: deriving on associated data types fails to find constraints -------------------------------------+------------------------------------- Reporter: mf825 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Type checker) | Keywords: TypeFamilies, | Operating System: Unknown/Multiple associated types, deriving | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeFamilies, UndecidableInstances #-} class D a where data DT a class C a where data CT a instance (D a, Eq (DT a)) => C (Maybe a) where data CT (Maybe a) = CTMaybe (DT a) deriving (Eq) {- $ stack --resolver=nightly-2017-10-20 exec -- ghc --version The Glorious Glasgow Haskell Compilation System, version 8.2.1 $ stack --resolver=nightly-2017-10-20 exec -- ghci Main.hs GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help (0.00 secs, 0 bytes) (0.00 secs, 0 bytes) (0.00 secs, 0 bytes) (0.00 secs, 0 bytes) (0.00 secs, 0 bytes) (0.00 secs, 0 bytes) (0.00 secs, 0 bytes) (0.00 secs, 0 bytes) Loaded GHCi configuration from /home/mf/.ghci [1 of 1] Compiling Main ( Main.hs, interpreted ) Main.hs:7:48: error: • No instance for (Eq (DT a)) arising from the first field of ‘CTMaybe’ (type ‘DT a’) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Eq (CT (Maybe a))) | 7 | data CT (Maybe a) = CTMaybe (DT a) deriving (Eq) | ^^ Failed, 0 modules loaded. (0.03 secs,) Prelude> -- if i remove the offending @deriving@ clause above and add this line, everything is fine. -- use -XFlexibleInstances -XStandaloneDeriving for this. deriving instance Eq (DT a) => Eq (CT (Maybe a)) -} }}} checked on linux with ghc8.0.2 and 8.2.1. thanks! and sorry if i've missed a previous report covering this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14462 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14462: deriving on associated data types fails to find constraints -------------------------------------+------------------------------------- Reporter: mf825 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: TypeFamilies, Resolution: | associated types, deriving 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): Looks ok to me. There's no reason that the context of the `C`-instance decl for `Maybe a` should be the same as that of the `Eq`-instance decl for `CT (Maybe a)`. As the message says, a standalone deriving declaration should do the job nicely. Did you try that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14462#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14462: deriving on associated data types fails to find constraints -------------------------------------+------------------------------------- Reporter: mf825 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: TypeFamilies, Resolution: | associated types, deriving 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 mf825): thanks for the quick feedback! i guess what confused me was my assumption that the instance decl context should be also the context of the data decl, but perhaps there is some good reason not to have that. sorry, my mistake. please close this issue. cheers! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14462#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14462: deriving on associated data types fails to find constraints -------------------------------------+------------------------------------- Reporter: mf825 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: TypeFamilies, Resolution: fixed | associated types, deriving 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 mf825): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14462#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14462: deriving on associated data types fails to find constraints -------------------------------------+------------------------------------- Reporter: mf825 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: TypeFamilies, Resolution: fixed | associated types, deriving 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): See also #4815 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14462#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC