Equality constraints and RankNTypes - how do I assist type inference

Hi, I have the following code, using equality constraints and (I believe) RankNTypes: {-# LANGUAGE MultiParamTypeClasses, TypeFamilies, RankNTypes, ExistentialQuantification #-} {-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-} -- import Math.Algebra.Group.PermutationGroup -- Vector space over field k with basis b data Vect k b = V [(b,k)] deriving (Eq,Show) data TensorBasis a b = T a b deriving (Eq, Ord, Show) -- Tensor product of two vector spaces type Tensor u v = (u ~ Vect k a, v ~ Vect k b) => Vect k (TensorBasis a b) -- ** class Algebra k v where -- "v is a k-algebra" unit :: k -> v mult :: Tensor v v -> v type GroupAlgebra k = Vect k Int -- (Permutation Int) instance Num k => Algebra k (GroupAlgebra k) where unit 0 = V [] unit x = V [(1,x)] mult (V ts) = V [(g*h,x) | (T g h, x) <- ts] Everything is fine except for the last line, which causes the following error message: Couldn't match expected type `Tensor (GroupAlgebra k) (GroupAlgebra k)' against inferred type `Vect k1 b' In the pattern: V ts In the definition of `mult': mult (V ts) = V [(g * h, x) | (T g h, x) <- ts] In the instance declaration for `Algebra k (GroupAlgebra k)' But according to me, I've told it that these two types are the same at the line marked -- ** How do I help it out with type inference? (It, in this case, is GHCi 6.12.1) Any ideas?

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 8/20/10 16:08 , DavidA wrote:
type Tensor u v = (u ~ Vect k a, v ~ Vect k b) => Vect k (TensorBasis a b) -- **
IIRC this actually substitutes as (forall k a b. (u ~ Vect k a, v ~ Vect k b) => Vect k (TensorBasis a b)) and the implicit forall will generally mess things up because it won't be floated out to the top level. (Or in other words, constraints in type declarations don't generally do what you intend.) - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkxvHvoACgkQIn7hlCsL25V7/gCgt9NaWZBFV7VFCYbs5Q6hqgGG ke0AoNFQU6VOXboK7daFI6IAgUiyKfGx =JL3q -----END PGP SIGNATURE-----

Brandon S Allbery KF8NH
type Tensor u v = (u ~ Vect k a, v ~ Vect k b) => Vect k (TensorBasis a b) -- **
IIRC this actually substitutes as
(forall k a b. (u ~ Vect k a, v ~ Vect k b) => Vect k (TensorBasis a b))
and the implicit forall will generally mess things up because it won't be floated out to the top level. (Or in other words, constraints in type declarations don't generally do what you intend.)
Thanks. Is it possible to elaborate a bit - I still don't really understand what goes wrong. And is there any way to fix it?

This works: -- Tensor product of two vector spaces type family Tensor u v :: * type instance Tensor (Vect k a) (Vect k b) = Vect k (TensorBasis a b) On Aug 21, 2010, at 9:15 AM, DavidA wrote:
Brandon S Allbery KF8NH
writes: type Tensor u v = (u ~ Vect k a, v ~ Vect k b) => Vect k (TensorBasis a b) -- **
IIRC this actually substitutes as
(forall k a b. (u ~ Vect k a, v ~ Vect k b) => Vect k (TensorBasis a b))
and the implicit forall will generally mess things up because it won't be floated out to the top level. (Or in other words, constraints in type declarations don't generally do what you intend.)
Thanks. Is it possible to elaborate a bit - I still don't really understand what goes wrong. And is there any way to fix it?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher http://w3future.com
participants (3)
-
Brandon S Allbery KF8NH
-
DavidA
-
Sjoerd Visscher