[GHC] #15664: Core Lint error
GHC
ghc-devs at haskell.org
Fri Sep 21 21:19:04 UTC 2018
#15664: Core Lint error
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.6.1-beta1
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 Iceland_jack):
Short version
{{{#!hs
{-# Language RankNTypes, TypeOperators, DataKinds, PolyKinds, GADTs,
TypeInType, TypeFamilies #-}
{-# Options_GHC -dcore-lint #-}
import Data.Kind
type family Apply (kind) (f :: kind) :: Type
data ApplyT(kind) :: kind -> Type
type f ~> g = (forall xx. f xx -> g xx)
unravel :: ApplyT(k) ~> Apply(k)
unravel = unravel
}}}
{{{
$ ghci -ignore-dot-ghci hs/443.hs
GHCi, version 8.7.20180828: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( hs/443.hs, interpreted )
*** Core Lint errors : in result of Desugar (before optimization) ***
<no location info>: warning:
In the type ‘forall k. ApplyT k ~> Apply k’
Un-saturated type application Apply k_a1y2
*** Offending Program ***
Rec {
$tcApplyT :: TyCon
[LclIdX]
$tcApplyT
= TyCon
14646326419187070856##
770477529860249545##
$trModule
(TrNameS "ApplyT"#)
1#
$krep_a1Ad
$krep_a1Ae [InlPrag=NOUSERINLINE[~]] :: KindRep
[LclId]
$krep_a1Ae = $WKindRepVar (I# 0#)
$krep_a1Ad [InlPrag=NOUSERINLINE[~]] :: KindRep
[LclId]
$krep_a1Ad = KindRepFun $krep_a1Ae krep$*
$trModule :: Module
[LclIdX]
$trModule = Module (TrNameS "main"#) (TrNameS "Main"#)
unravel :: forall k. ApplyT k ~> Apply k
[LclIdX]
unravel
= \ (@ k_a1zb) (@ (xx_a1zc :: k_a1zb)) ->
break<0>() unravel @ k_a1zb @ xx_a1zc
end Rec }
*** End of Offense ***
<no location info>: error:
Compilation had errors
*** Exception: ExitFailure 1
>
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15664#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list