[GHC] #10361: DeriveAnyClass does not fill in associated type defaults
GHC
ghc-devs at haskell.org
Tue Sep 8 13:31:33 UTC 2015
#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
More information about the ghc-tickets
mailing list