[GHC] #11534: Allow class associated types to reference functional dependencies

GHC ghc-devs at haskell.org
Wed Feb 3 22:37:30 UTC 2016


#11534: Allow class associated types to reference functional dependencies
-------------------------------------+-------------------------------------
        Reporter:  ekmett            |                Owner:
            Type:  feature request   |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler (Type    |              Version:  7.10.3
  checker)                           |             Keywords:  TypeFamilies,
      Resolution:                    |  FunctionalDependencies
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  Other             |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by ekmett):

 If I define

 {{{#!hs
 class Functor (c :: i -> i -> *) (d :: j -> j -> *) (f :: i -> j) | f -> c
 d
 }}}

 as opposed to

 {{{#!hs
 class Functor (f :: i -> j) where
   type Dom f :: i -> i -> *
   type Cod f :: j -> j -> *
 }}}

 then I go to define a subclass of `Functor`, I need to repeat `c` and `d`.

 {{{#!hs
 class Functor c d f => Faithful c d f | f -> c d
 }}}

 In some real world code I have this eventually swells to something like
 8-9 parameters, which is clearly unwieldy.

 I can "lower" things back down, by using

 {{{#!hs
 class (c ~ Dom f, d ~ Cod f) => Functor (c :: i -> i -> *) (d :: j -> j ->
 *) (f :: i -> j) | f -> c d where
   type Dom f :: i -> i -> *
   type Cod f :: j -> j -> *
   fmap :: c a b -> d (f a) (f b)
 }}}

 and using something like

 {{{#!hs
 type Fun f = Functor (Dom f) (Cod f) f
 }}}

 as the superclass of

 {{{#!hs
 class Fun f => Faithful f where
   unfmap :: Cod f (f a -> f b) -> Dom f a b
 }}}

 at the cost of repeating myself between the fundep determined argument and
 the class associated type in every instance.

 {{{#!hs
 instance Functor (->) (->) ((->) e) where
   type Dom ((->) e) = (->)
   type Cod ((->) e) = (->)
   fmap = (.)
 }}}

 In the example from #11523, I have

 {{{#!hs
 instance (Category p, Category q) => Category (Nat p q) where
   type Ob (Nat p q) = Functor p q
 }}}

 Note: I can't run the trick the other way and put a type synonym there,
 since I can't partially apply it.

 which requires me to use functional dependencies for the definition of
 Functor or to be able to use the existing class/instance synonym trick
 mentioned there, which #11523 notes currently sends the compiler into a
 spin with `UndecidableSuperClasses` turned on.

 With the machinery I was seeking here, we'd be able to write just

 {{{#!hs
 instance Functor (->) (->) ((->) e) where
   fmap = (.)
 }}}

 but as you note this would require upgrading functional dependencies.

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


More information about the ghc-tickets mailing list