[GHC] #14668: Ordering of declarations can cause typechecking to fail
GHC
ghc-devs at haskell.org
Mon Feb 12 13:31:27 UTC 2018
#14668: Ordering of declarations can cause typechecking to fail
-------------------------------------+-------------------------------------
Reporter: heptahedron | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.1
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by danilo2):
Hi! Yet another example which seems related! If you move the data
declaration to be the first line, it compiles fine:
{{{
{-# LANGUAGE TypeInType #-}
module Type.Data.Map where
import Prelude
import Data.Kind
type family KeyKind (obj :: Type) :: Type
type family ValKind (obj :: Type) :: Type
type family Get (key :: KeyKind a) (obj :: a) :: ValKind a
data Map (k :: Type) (v :: Type) = Map [(k,v)]
type instance Get k ('Map ('(k,v) ': _)) = v
type instance KeyKind (Map k v) = k
type instance ValKind (Map k v) = v
}}}
Otherwise it gives error:
{{{
Main.hs:16:19: error:
• Occurs check: cannot construct the infinite kind:
k0 ~ KeyKind (Map k0 v0)
The type variables ‘v0’, ‘k0’ are ambiguous
• In the first argument of ‘Get’, namely ‘k’
In the type instance declaration for ‘Get’
|
16 | type instance Get k ('Map ('(k,v) ': _)) = v
| ^
Main.hs:16:44: error:
• Occurs check: cannot construct the infinite kind:
v0 ~ ValKind (Map k0 v0)
The type variables ‘k0’, ‘v0’ are ambiguous
• In the type ‘v’
In the type instance declaration for ‘Get’
|
16 | type instance Get k ('Map ('(k,v) ': _)) = v
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14668#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list