[GHC] #12668: Program that fails Core Lint terribly
GHC
ghc-devs at haskell.org
Thu Oct 6 16:50:31 UTC 2016
#12668: Program that fails Core Lint terribly
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by bgamari:
@@ -21,3 +21,3 @@
- GHC 465c6c5d15f8fb54afb78408f3a79e75e74d2cd4 seems to let this program
- typecheck, but if you enable Core Lint it soon becomes clear that not all
- is well. Here's a sampling of the carnage,
+ GHC 465c6c5d15f8fb54afb78408f3a79e75e74d2cd4 and 8.0.1 seem to let this
+ program typecheck, but if you enable Core Lint it soon becomes clear that
+ not all is well. Here's a sampling of the carnage,
New description:
While looking for a testcase for another unrelated compiler bug (see
Phab:D2577) I had the pleasure of encountering this specimen,
{{{#!hs
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE RankNTypes #-}
module Hi where
import GHC.Exts
data Some r = Some (TYPE r -> TYPE r)
doSomething :: forall (r :: RuntimeRep). forall (a :: TYPE r). ()
=> Int -> (a -> Int) -> a -> a
doSomething n f =
case n of
1 -> error "hello"
3 -> error "hello"
}}}
GHC 465c6c5d15f8fb54afb78408f3a79e75e74d2cd4 and 8.0.1 seem to let this
program typecheck, but if you enable Core Lint it soon becomes clear that
not all is well. Here's a sampling of the carnage,
{{{
$ ghc hi.hs -fforce-recomp -dcore-lint -O0
[1 of 1] Compiling Hi ( hi.hs, hi.o )
*** Core Lint errors : in result of Desugar (after optimization) ***
<no location info>: warning:
In the type ‘a_a2ON -> Int’
Ill-kinded argument in type or kind ‘a_a2ON -> Int’
type or kind ‘a_a2ON -> Int’ kind: TYPE r_a2OM
<no location info>: warning:
In the type ‘a_a2ON -> a_a2ON’
Ill-kinded argument in type or kind ‘a_a2ON -> a_a2ON’
type or kind ‘a_a2ON -> a_a2ON’ kind: TYPE r_a2OM
<no location info>: warning:
In the type ‘a_a2ON -> a_a2ON’
Ill-kinded argument in type or kind ‘a_a2ON -> a_a2ON’
type or kind ‘a_a2ON -> a_a2ON’ kind: TYPE r_a2OM
<no location info>: warning:
In the expression: patError
@ 'PtrRepLifted @ (a_a2ON -> a_a2ON)
"hi.hs:(12,5)-(14,24)|case"#
Ill-kinded argument in type or kind ‘a_a2ON -> a_a2ON’
type or kind ‘a_a2ON -> a_a2ON’ kind: TYPE r_a2OM
...
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12668#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list