[Haskell-cafe] Could FDs help usurp an ATs syntactic restriction?

Nicolas Frisby nicolas.frisby at gmail.com
Thu Dec 4 22:38:03 EST 2008


>From the error below, I'm inferring that the RHS of the associated
type definition can only contain type variables from the instance
head, not the instance context. I didn't explicitly see this
restriction when reading the GHC/Type_families entry.

Could perhaps the "a b -> bn" functional dependency of the TypeEq
class lift this restriction for bn? This isn't my ball park, but that
idea has my hopes up :).

<haskell>
{-# LANGUAGE TypeFamilies #-}

import TypeEq

-- Attempting to encapsulate TypeEq behind an associated type.

class EQ a b where
  type BN a b

instance TypeEq a b bn => EQ a b where
  type BN a b = bn
</haskell>

results in an error

<ghci>
  /tmp/Test.hs:9:16: Not in scope: type variable `bn'
  Failed, modules loaded: none.
</ghci>


More information about the Haskell-Cafe mailing list