[GHC] #16008: GHC HEAD type family regression involving invisible arguments
GHC
ghc-devs at haskell.org
Fri Dec 7 19:13:01 UTC 2018
#16008: GHC HEAD type family regression involving invisible arguments
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.8.1
Component: Compiler | Version: 8.7
(Type checker) |
Keywords: TypeFamilies, | Operating System: Unknown/Multiple
TypeInType |
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code compiles on GHC 8.0.2 through 8.6.2:
{{{#!hs
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
class C k where
type S :: k -> Type
data D :: Type -> Type
data SD :: forall a. D a -> Type
instance C (D a) where
type S = SD
}}}
But fails to compile on GHC HEAD (commit
73cce63f33ee80f5095085141df9313ac70d1cfa):
{{{
$ ~/Software/ghc2/inplace/bin/ghc-stage2 Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:15:3: error:
• Type indexes must match class instance head
Expected: S @(D a)
Actual: S @(D a1)
• In the type instance declaration for ‘S’
In the instance declaration for ‘C (D a)’
|
15 | type S = SD
| ^^^^^^^^^^^
}}}
This regression prevents
[https://cs.brynmawr.edu/~rae/papers/2018/stitch/stitch.tar.gz the stitch
library] from compiling.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16008>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list