[GHC] #13267: Constraint synonym instances

GHC ghc-devs at haskell.org
Sat Feb 11 04:04:01 UTC 2017


#13267: Constraint synonym instances
-------------------------------------+-------------------------------------
           Reporter:  ezyang         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC accepts
  Unknown/Multiple                   |  invalid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Something funny happens when you try to declare an instance of a
 constraint synonym:

 {{{
 {-# LANGUAGE ConstraintKinds #-}
 module F where

 type ShowF a = Show (a -> Bool)

 instance ShowF Int where
     show _ = "Fun"
 }}}

 I get:

 {{{
 F.hs:8:5: error: ‘show’ is not a (visible) method of class ‘ShowF’
   |
 8 |     show _ = "Fun"
   |     ^^^^
 }}}

 OK, but it gets weirder. Look at:

 {{{
 {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances #-}
 module F where

 type ShowF a = (Show (a -> Bool))

 instance ShowF Int where
 }}}

 This is accepted (with a complaint that `show` is not implemented.) It
 gets even more awful:

 {{{
 {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances,
 MultiParamTypeClasses #-}
 module F where

 type ShowF a = (Show Bool, Show Int)

 instance ShowF Int where
 }}}

 This is awful: GHC treats `Show Bool` and `Show Int` as if they were
 constraints, and then emits the following DFun:

 {{{
 df9d1b4635f2a752f29ff327ab66d1cb
   $f(%,%)ShowShow :: (Show Bool, Show Int)
   DFunId
   {- Strictness: m, Inline: CONLIKE,
      Unfolding: DFun: @ a @ b.
                   @ (Show Bool) @ (Show Int) $fShowBool $fShowInt -}

 }}}

 I don't even know what this is supposed to mean.

 OK, so what should we do? I think there are a few possibilities:

 1. Completely outlaw instance declarations on constraint synonyms.

 2. Allow instance declarations on constraint synonyms, but only if after
 desugaring the synonym, you end up with a single class head. I would find
 this useful in a few cases, for example, if you are writing `instance
 MonadSample (Impl t) MyMonad`, if you had `type MonadSample2 t a =
 MonadSample (Impl t) a` you might prefer writing `instance MonadSample t
 MyMonad` instead

 3. Figure out what instance declarations with multiple class heads, and
 proceed accordingly.

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


More information about the ghc-tickets mailing list