Superclass Equality constraints cp FunDeps

Anthony Clayden anthony_clayden at clear.net.nz
Sat Apr 29 05:55:14 UTC 2017


> On Sat Apr 29 02:23:10 UTC 2017, Richard Eisenberg wrote: 
>
> I'm not quite sure what a restriction on (~) might be,

Thanks Richard,

I was thinking that FunDeps are restricted to bare type
vars.

I can't write either of these:

> class C a b c | a -> (b, c)   -- per my O.P. (~)

> class C a b c | a -> (b c)

So it's the one place where type vars `b c` like this:

> class C a b c | a -> b c

doesn't mean applying `b` to `c`.


> but (~) is effectively declared as
> 
> > class a ~ b | a -> b, b -> a
> 
> So I agree with your observations.

Aha! So I could equivalently go:

> class EqC a b | a -> b, b -> a
>
> class (EqC a (b, c)) => C a b c where ...
>   -- needs FlexibleInstances

And that does indeed work equivalently to the (~).
Again, I haven't put FunDeps on class `C`.

So should I reasonably have known that
a superclass constraint 
with FunDeps on the superclass
induces FunDeps on the sub-class
without explicitly needing to declare so?

(I'm not complaining, more surprised/impressed.)


AntC

> > On Apr 27, 2017, at 8:14 PM, Anthony Clayden
> > <anthony_clayden at clear.net.nz> wrote: 
> > The docos say [User Guide 10.14.1. on Equality
> > Constraints] 
> >> Equality constraints can also appear in class and
> > instance contexts.
> >> The former enable a simple translation of programs
> >> using functional dependencies into programs using
> > family synonyms instead. 
> >
>
http://downloads.haskell.org/~ghc/8.0.2/docs/html/users_guide/glasgow_exts.html#equality-constraints
> > 
> > And the forms of constraint seem quite sophisticated.
> > I was surprised (pleased) I could do this:
> > 
> > {-# LANGUAGE   MultiParamTypeClasses, TypeFamilies,
> >                             FlexibleInstances #-}
> > 
> > type family F a
> > 
> > class (F a ~ (b, c) ) => C a b c   where       -- (b c)
> >  !! f1 :: a -> b
> >  f2 :: a -> c
> > 
> > Uses of `f1` happily improve the type for `b`.
> > Uses of `f2` happily improve the type for `c`.
> > 
> > But I didn't declare a Functional Dependency.
> > (It seems to do no harm if I add `| a -> b c`.)
> > 
> > GHC's behaviour seems stronger than a "simple
> > translation". It seems entirely equivalent to a FunDep.
> > 
> > Or is there something I'm missing?
> > (I could have overlapping instances,
> > but only providing the equations for
> > type family `F` are confluent.)
> > 
> > Are there restrictions on the form of Equality
> > Constraints to get them to behave as FunDeps?
> > (It's not merely a bare typevar on one side.)
> > 
> > AntC
> > _______________________________________________
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users at haskell.org
> >
>
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
> 


More information about the Glasgow-haskell-users mailing list