[GHC] #10361: DeriveAnyClass does not fill in associated type defaults

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I would expect `test1` and `test2` below to typecheck. This is a reduced test case from trying to use `DeriveAnyClass` on the `Generic` class of the `generics-sop` package, which unfortunately fails due to this bug. {{{ {-# LANGUAGE DeriveAnyClass, StandaloneDeriving, TypeFamilies #-} module Test where class C1 a where type T1 a type instance T1 a = Char class C2 a where -- equivalent to C1 type T2 a type instance T2 a = Char class C3 a where -- equivalent to C1, C2 type T3 a type instance T3 a = Char data A = B deriving C1 deriving instance C2 A instance C3 A -- fails -- test1 :: T1 A -- test1 = 'x' -- fails -- test2 :: T2 A -- test2 = 'x' -- succeeds test3 :: T3 A test3 = 'x' }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Changes (by kosmikus): * failure: None/Unknown => GHC rejects valid program * component: Compiler => Compiler (Type checker) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => dreixel Comment: Pedro, this is your bag, right? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by dreixel): I agree that this is a bug, yes. Not entirely sure when I will have time to fix it, though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by vagarenko): My case of this bug: {{{ {-# LANGUAGE DefaultSignatures, TypeFamilies, TypeOperators, FlexibleContexts, DeriveGeneric, DeriveAnyClass #-} module Bug where import GHC.Generics --------------------------------------------------------------------- class Convert a where type Result a type instance Result a = GResult (Rep a) convert :: a -> Result a default convert :: (Generic a, GConvert (Rep a)) => a -> GResult (Rep a) convert x = gconvert (from x) instance Convert Float where type Result Float = Float convert = id instance Convert Int where type Result Int = Int convert = id --------------------------------------------------------------------- class GConvert f where type GResult f gconvert :: f p -> GResult f instance (Convert c) => GConvert (K1 i c) where type GResult (K1 i c) = Result c gconvert (K1 x) = convert x instance (GConvert f) => GConvert (M1 i t f) where type GResult (M1 i t f) = GResult f gconvert (M1 x) = gconvert x instance (GConvert f, GConvert g) => GConvert (f :*: g) where type GResult (f :*: g) = (GResult f, GResult g) gconvert (x :*: y) = (gconvert x, gconvert y) --------------------------------------------------------------------- -- This works: data Data1 = Data1 Int Float deriving (Generic) instance Convert Data1 val :: (Int, Float) val = convert $ Data1 0 0.0 -- This doesn't: data Data2 = Data2 Int Float deriving (Generic, Convert) -- Couldn't match type `Result Data' with `(Int, Float)' -- Expected type: Data -> Result Data -- Actual type: Data -> GResult (Rep Data) -- In the expression: Bug.$gdmconvert -- In an equation for `convert': convert = Bug.$gdmconvert -- When typechecking the code for `convert' -- in a derived instance for `Convert Data': -- To see the code I am typechecking, use -ddump-deriv }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by vagarenko): * cc: vagarenko (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1283 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D1283 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults
-------------------------------------+-------------------------------------
Reporter: kosmikus | Owner: dreixel
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1283
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1283 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1283 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Generics -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10361: DeriveAnyClass does not fill in associated type defaults -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: dreixel Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Generics, Resolution: fixed | deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1283 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: Generics => Generics, deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10361#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC