[GHC] #11348: Local open type families instances ignored during type checking
GHC
ghc-devs at haskell.org
Mon Jan 4 18:53:49 UTC 2016
#11348: Local open type families instances ignored during type checking
-------------------------------------+-------------------------------------
Reporter: alexvieth | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# 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!
{{{#!sh
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.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11348>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list