[GHC] #15979: Core Lint error with LiberalTypeSynonyms

GHC ghc-devs at haskell.org
Fri Nov 30 17:48:50 UTC 2018


#15979: Core Lint error with LiberalTypeSynonyms
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.8.1
          Component:  Compiler       |           Version:  8.6.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE LiberalTypeSynonyms #-}
 {-# LANGUAGE PolyKinds #-}
 {-# OPTIONS_GHC -dcore-lint #-}
 module Bug where

 import Data.Kind

 type KindOf (a :: k) = k

 wat :: KindOf (forall (a :: ()). a)
 wat = ()
 }}}
 {{{
 $ /opt/ghc/8.6.2/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
 *** Core Lint errors : in result of Desugar (before optimization) ***
 <no location info>: warning:
     In the type ‘KindOf (forall (a :: ()). a)’
     Non-*-like kind when *-like expected: ()
     when checking the body of forall: forall (a :: ()). a
 *** Offending Program ***
 Rec {
 $trModule :: Module
 [LclIdX]
 $trModule = Module (TrNameS "main"#) (TrNameS "Bug"#)

 wat :: KindOf (forall (a :: ()). a)
 [LclIdX]
 wat = ()
 end Rec }

 *** End of Offense ***


 <no location info>: error:
 Compilation had errors
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15979>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list