[GHC] #11732: Deriving Generic1 interacts poorly with TypeInType
GHC
ghc-devs at haskell.org
Tue Mar 29 17:39:29 UTC 2016
#11732: Deriving Generic1 interacts poorly with TypeInType
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords: TypeInType,
| Generics
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 RyanGlScott):
Replying to [comment:13 goldfire]:
> This all means we can just do nothing about this particular issue. Which
is nice.
That is nice!
What then, should we do about this program? (from
[https://mail.haskell.org/pipermail/ghc-devs/2016-March/011645.html here])
{{{#!hs
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeInType #-}
module Cat where
import Data.Kind
class Cat k (cat :: k -> k -> *) where
catId :: cat a a
catComp :: cat b c -> cat a b -> cat a c
instance Cat * (->) where
catId = id
catComp = (.)
newtype Fun a b = Fun (a -> b) deriving (Cat k)
}}}
Currently, this generates an instance of the form `instance Cat * Fun`
(i.e., the same thing as if you had written `deriving (Cat *)`. Would this
be acceptable?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11732#comment:14>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list