Deriving clauses can have forall types
I made a horrifying discovery today: GHC accepts this code!
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# OPTIONS_GHC -ddump-deriv #-}
module Bug1 where
class C a b
data D a = D deriving ((forall a. C a))
GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug1 ( Bug.hs, interpreted )
==================== Derived instances ====================
Derived class instances:
instance Bug1.C a1 (Bug1.D a2) where
Derived type family instances:
Ok, 1 module loaded.
It gets even worse with this example:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeInType #-}
{-# OPTIONS_GHC -ddump-deriv -fprint-explicit-kinds #-}
module Bug1 where
import Data.Kind
import GHC.Generics
data Proxy (a :: k) = Proxy
deriving ((forall k. (Generic1 :: (k -> Type) -> Constraint)))
GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug1 ( Bug.hs, interpreted )
==================== Derived instances ====================
Derived class instances:
instance GHC.Generics.Generic1 k (Bug1.Proxy k) where
GHC.Generics.from1 x_a3ip
= GHC.Generics.M1
(case x_a3ip of { Bug1.Proxy -> GHC.Generics.M1 GHC.Generics.U1 })
GHC.Generics.to1 (GHC.Generics.M1 x_a3iq)
= case x_a3iq of {
(GHC.Generics.M1 GHC.Generics.U1) -> Bug1.Proxy }
Derived type family instances:
type GHC.Generics.Rep1 k_a2mY (Bug1.Proxy k_a2mY) = GHC.Generics.D1
k_a2mY
('GHC.Generics.MetaData
"Proxy" "Bug1" "main" 'GHC.Types.False)
(GHC.Generics.C1
k_a2mY
('GHC.Generics.MetaCons
"Proxy"
'GHC.Generics.PrefixI
'GHC.Types.False)
(GHC.Generics.U1 k_a2mY))
Ok, 1 module loaded.
In this example, the forall
'd k
from the deriving
clause is discarded and then unified with the k
from data Proxy (a :: k)
.
All of this is incredibly unsettling. We really shouldn't be allowing forall
types in deriving
clauses in the first place.
Trac metadata
Trac field | Value |
---|---|
Version | 8.2.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (Type checker) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |