Superclass Equality constraints cp FunDeps
Anthony Clayden
anthony_clayden at clear.net.nz
Fri Apr 28 00:14:49 UTC 2017
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
More information about the Glasgow-haskell-users
mailing list