Local open type families instances ignored during type checking
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeInType #-}
import Data.Kind
import Data.Proxy
type family TrivialFamily t :: Type
type instance TrivialFamily (t :: Type) = Bool
data R where
R :: Proxy Bool -> R
type ProblemType t = 'R ('Proxy :: Proxy (TrivialFamily t))
Compiling this program as-is, GHC rejects it!
error:
• Expected kind ‘Proxy Bool’,
but ‘'Proxy’ has kind ‘Proxy (TrivialFamily t)’
• In the first argument of ‘R’, namely
‘(Proxy :: Proxy (TrivialFamily t))’
In the type ‘R (Proxy :: Proxy (TrivialFamily t))’
In the type declaration for ‘ProblemType’
But if we move TrivialFamily
to another module and import it, GHC discovers that TrivialFamily t = Bool
and the program is accepted.
When compiling the rejected program (with the local family instance) I observe that the instance environments given by FamInst.tcGetFamInstEnvs
contain no instances! The renamer processes the local instance, but no FamInst
is created for it, and nothing enters the TcGblEnv
's family instance record.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1-rc1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |