[GHC] #13788: TypeInType fails to compile old code
GHC
ghc-devs at haskell.org
Mon Jun 5 12:14:44 UTC 2017
#13788: TypeInType fails to compile old code
-------------------------------------+-------------------------------------
Reporter: br1 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1-rc2
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:
-------------------------------------+-------------------------------------
{{{
{-# LANGUAGE TypeInType #-}
module PP where
newtype Field l v = Field { value :: v }
label :: Field l v -> l
label = undefined
class HEq x
hEq :: HEq x => x -> Int
hEq = undefined
class HListGet r where
hListGet :: r -> Int
instance
HEq l => HListGet (Field l v) where
hListGet f = hEq (label f)
}}}
fails with
{{{
mini.hs:18:29: error:
• Couldn't match type ‘k’ with ‘*’
‘k’ is a rigid type variable bound by
the instance declaration at mini.hs:17:5-33
Expected type: Field * l v
Actual type: Field k l v
• In the first argument of ‘label’, namely ‘f’
In the first argument of ‘hEq’, namely ‘(label f)’
In the expression: hEq (label f)
• Relevant bindings include
f :: Field k l v (bound at mini.hs:18:14)
hListGet :: Field k l v -> Int (bound at mini.hs:18:5)
|
18 | hListGet f = hEq (label f)
|
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13788>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list