[GHC] #11250: GHC shows core with error
GHC
ghc-devs at haskell.org
Fri Dec 18 03:08:18 UTC 2015
#11250: GHC shows core with error
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect
Unknown/Multiple | warning at compile-time
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code intentionally does not compile:
{{{
{-# LANGUAGE DataKinds, KindSignatures, PolyKinds #-}
data Proxy (p :: k) = Proxy
data Tagged (t :: k) s = Tagged s
proxy :: Tagged t s -> Proxy t -> s
proxy = undefined
bar :: Tagged (gad :: *) Int
bar = undefined
foo :: Int
foo = proxy bar (Proxy::Proxy 'True)
}}}
but it produces the following output with GHC and GHCi:
{{{
[1 of 1] Compiling Main ( Bug.hs, interpreted )
RAE1
[W] cobox_aLM :: t0_aK4[tau:1] ~ 'True (CNonCanonical)
t0_aK4[tau:1]
'True
False
Bug.hs:13:18:
Couldn't match kind ‘Bool’ with ‘*’
Expected type: Proxy t0
Actual type: Proxy 'True
In the second argument of ‘proxy’, namely ‘(Proxy :: Proxy True)’
In the expression: proxy bar (Proxy :: Proxy True)
In an equation for ‘foo’: foo = proxy bar (Proxy :: Proxy True)
Failed, modules loaded: none.
}}}
This ticket is about the first block printed out. It seems to be a random
section of core, and is completely useless to debugging the problem.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11250>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list