type families not advertised for 6.8
Wolfgang Jeltsch
g9ks157k at acme.softbase.org
Fri Oct 19 04:50:45 EDT 2007
Am Freitag, 19. Oktober 2007 09:25 schrieb Simon Peyton-Jones:
> […]
> Our current plan is to regard FDs as syntactic sugar for indexed type
> families. We think this can be done -- see our IFL workshop paper
> http://research.microsoft.com/%7Esimonpj/papers/assoc-types
I doubt this can be done in all cases. Take the following code which is more
or less from HList:
{-# LANGUAGE
MultiParamTypeClasses,
FunctionalDependencies,
FlexibleInstances,
OverlappingInstances,
UndecidableInstances,
TypeFamilies,
EmptyDataDecls
#-}
data False
data True
class TypeEq t1 t2 b | t1 t2 -> b where
typeEq :: t1 -> t2 -> b
instance TypeEq t t True where
typeEq = undefined
instance (b ~ False) => TypeEq t1 t2 b where
typeEq = undefined
If you convert this code according to the above-cited paper to use type
families instead of functional dependencies, you run into several problems.
First, type families don’t allow overlapping with conflicting results.
Interestingly, the compiler doesn’t complain about the overlapping but about
two other things. In the first instance declaration you have something like
type TypeEqTF t t = True
which results in the error “Conflicting definitions for `t'”. In addition,
the second instance declaration which includes something like
type TypeEqTF t1 t2 = b
causes the error “Not in scope: type variable `b'”. This latter problem can
be circumvented by writing
type TypeEqTF t1 t2 = False
but it shows that the automatic translation doesn’t work here.
In fact, after thinking and experimenting I came to the conclusion that it’s
probably just not possible to define a type function TypeEqTF t1 t2 which for
*all* types t1 and t2 yields True or False, depending on whether t1 and t2
are equal or not.
> […]
> Simon
Best wishes,
Wolfgang
More information about the Glasgow-haskell-users
mailing list