[GHC] #15076: Typed hole with higher-rank kind causes GHC to panic (No skolem info)
GHC
ghc-devs at haskell.org
Mon Apr 23 16:20:43 UTC 2018
#15076: Typed hole with higher-rank kind causes GHC to panic (No skolem info)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.2.2
checker) | Keywords: TypedHoles,
Resolution: | TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: #14040, #14880 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
If you don't use a typed hole:
{{{#!hs
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
import Data.Proxy
foo :: forall (a :: Type)
(f :: forall (x :: a). Proxy x -> Type).
Proxy f -> ()
foo _ = ()
}}}
Then it compiles. However, it fails with a Core Lint error:
{{{
$ /opt/ghc/8.4.2/bin/ghc Bug.hs -dcore-lint
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
*** Core Lint errors : in result of Desugar (after optimization) ***
<no location info>: warning:
In the type ‘forall (x :: a) a (f :: forall (x :: a).
Proxy x -> *).
Proxy (f x) -> ()’
@ a_aZi[sk:1] is out of scope
*** Offending Program ***
foo
:: forall (x :: a) a (f :: forall (x :: a). Proxy x -> *).
Proxy (f x) -> ()
[LclIdX]
foo
= \ (@ (x_a1e5 :: a_aZi[sk:1]))
(@ a_a1e6)
(@ (f_a1e7 :: forall (x :: a). Proxy x -> *))
_ [Occ=Dead] ->
()
$trModule :: Module
[LclIdX]
$trModule = Module (TrNameS "main"#) (TrNameS "Bug"#)
*** End of Offense ***
<no location info>: error:
Compilation had errors
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15076#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list