[GHC] #16255: Visible kind application defeats type family with higher-rank result kind

GHC ghc-devs at haskell.org
Tue Jan 29 16:00:50 UTC 2019


#16255: Visible kind application defeats type family with higher-rank result kind
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.7
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
  TypeApplications, TypeFamilies     |
       Architecture:                 |   Type of failure:  GHC accepts
  Unknown/Multiple                   |  invalid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #15740
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 After #15740, GHC now (correctly) rejects this program:

 {{{#!hs
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE TypeFamilies #-}
 module Bug where

 import Data.Kind

 data SBool :: Bool -> Type
 type family F :: forall k. k -> Type where
   F = SBool
 }}}
 {{{
 $ ~/Software/ghc5/inplace/bin/ghc-stage2 --interactive Bug.hs
 GHCi, version 8.7.20190115: https://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )

 Bug.hs:12:7: error:
     • Expected kind ‘forall k. k -> *’,
         but ‘SBool’ has kind ‘Bool -> *’
     • In the type ‘SBool’
       In the type family declaration for ‘F’
    |
 12 |   F = SBool
    |       ^^^^^
 }}}

 However, there's a very simple way to circumvent this: add a visible kind
 application to `F`'s equation.

 {{{#!hs
 type family F :: forall k. k -> Type where
   F @Bool = SBool
 }}}

 If I understand things correctly, GHC shouldn't allow this.

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


More information about the ghc-tickets mailing list