[GHC] #14332: Deriving clauses can have forall types
GHC
ghc-devs at haskell.org
Mon Oct 9 12:42:31 UTC 2017
#14332: Deriving clauses can have forall types
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.1
checker) |
Resolution: | Keywords: deriving
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Replying to [comment:7 simonpj]:
> I'd say this is an outright bug. You should say
> {{{
> data D = D deriving (C Type)
> }}}
> Would you like to open a ticket?
No, because this is behaving as I would expect it to! Kind unification is
fundamental to the way `deriving` works, and I'm leery of any design which
doesn't incorporate it as a guiding principle. Here is another example
where `deriving` //must// unify kinds:
{{{#!hs
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeInType #-}
{-# OPTIONS_GHC -ddump-deriv #-}
data Proxy k (a :: k) = Proxy deriving Functor
}}}
{{{
GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/ryanglscott/.ghci
[1 of 1] Compiling Main ( Bug.hs, interpreted )
==================== Derived instances ====================
Derived class instances:
instance GHC.Base.Functor (Main.Proxy *) where
}}}
Here, if `k` weren't unified with `*`, then the instance simply wouldn't
be well kinded.
How about another example?
{{{#!hs
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeInType #-}
{-# OPTIONS_GHC -ddump-deriv #-}
import Data.Kind
class C k (f :: k -> *)
data T j (a :: j) deriving (C k)
}}}
{{{
GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/ryanglscott/.ghci
[1 of 1] Compiling Main ( Bug.hs, interpreted )
==================== Derived instances ====================
Derived class instances:
instance Main.C k (Main.T k) where
}}}
Notice that GHC didn't attempt to emit an instance of the form `forall k
j. C k (T j)`—instead, it deliberately unified `k` and `j`! This is a good
thing, because otherwise GHC would spit out utter nonsense that wouldn't
pass muster.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14332#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list