[GHC] #13047: Can create bindings of kind Constraint without ConstraintKind, only TypeFamilies

GHC ghc-devs at haskell.org
Sat Dec 31 17:06:58 UTC 2016


#13047: Can create bindings of kind Constraint without ConstraintKind, only
TypeFamilies
-------------------------------------+-------------------------------------
           Reporter:  pggiarrusso    |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This code compiles with GHC 8.0.1 (in either variant, with or without the
 definition of ApplyCtx Int in Foo Int. I think it shouldn't according to
 the docs in
 http://ghc.readthedocs.io/en/master/glasgow_exts.html?highlight=constraintKinds
 #the-constraint-kind. If this is intended, I guess documenting it is
 acceptable.
 {{{
 {-# LANGUAGE TypeFamilies #-}
 module Foo where

 import GHC.Exts (Constraint)
 class Foo a where
   type ApplyCtx a :: Constraint
   type ApplyCtx a = ()

 instance Foo Int where
   type ApplyCtx Int = Show Int -- Commenting this out makes no difference.

 f :: ApplyCtx Int => Int
 f = 0
 }}}

 Googling found https://mail.haskell.org/pipermail/glasgow-haskell-
 users/2016-February/026151.html, but seems a different issue (and a non-
 bug).
 Also found https://ghc.haskell.org/trac/ghc/ticket/11715, which might be
 relevant (or not).

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


More information about the ghc-tickets mailing list