Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Edgar Gomes Araujo
Dear Stephan, Finally It's alive and working, huhhuu! After 3 long days... As predictable, it was my fault. There was basically two big mistakes: - splitAF::(SubUnit a b, Ord a)=>BoxPair -> ActiveSubUnit a -> StateMBC a () instead of "splitAF::(SubUnit a, Ord a)=> BoxPair -> a -> StateMBC a

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Stephen Tetley
Hi Edgar I think you have some errors of construction rather than just a problem with the type families / fun deps. Note, I've knocked off the class constraints on the data declarations on the copy I'm working with (e.g ActiveSubUnit) , this may or may not change things. This change to splitAF w

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Edgar Gomes Araujo
@ Stephem: here is my build-depends: Vec -any, array -any, base -any, containers -any, mtl -any. You also can find a cabal file on my GitHub: http://github.com/EdgarGomes/DeUni @Daniel: In fact, I've inserted that context trying to fix the problem but it affect

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Daniel Fischer
On Saturday 26 March 2011 21:35:13, Edgar Gomes Araujo wrote: > Hi Stephen, > I've have done the following: > > {-# LANGUAGE ScopedTypeVariables #-} > {-# LANGUAGE RankNTypes #-} > ... > mbc :: forall a . (SubUnit a)=>[Point] -> SetActiveSubUnits a -> Box -> > StateMBC a [Unit a] > mbc p afl box =

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Edgar Gomes Araujo
Hi Stephen, I've have done the following: {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-} ... mbc :: forall a . (SubUnit a)=>[Point] -> SetActiveSubUnits a -> Box -> StateMBC a [Unit a] mbc p afl box = do cleanAFLs if (null afl) then do (unit, afl') <-

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Stephen Tetley
Hi Edgar On 26 March 2011 20:19, Stephen Tetley wrote: > ... you > want to use scoped type variables so that the local type annotation is > *the same type* type variable. Ahem ... > so that the local type annotation is *the same type variable*. Where is Data.Vec coming from so I can try to com

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Stephen Tetley
Hi Edgar What did you try? My intuition is that this specific bit (there may be other problems) is because the type checker is introducing a new type variable. Thus you don't actually want the type operator (~) to say the new type variable is equal to the type variable in the function signature,

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Edgar Gomes Araujo
Unfortunately it didn't work. The error message is not so clear to me and my understanding in advanced Haskell type system is yet to weak to figure out what is going on. Looking at the error messages seems that the type inference analyzes the code in two different direction and finds some inconsis

Re: [Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Stephen Tetley
For the specific error at line 265 I think you should be using ScopedTypeVariables and properly qualifying the type signature at the function level with a forall. The local annotation { ::(SubUnit a)=> } is presumably introducing another type variable unrelated to 'a' in the function level type si

[Haskell-cafe] Functional dependence nightmare

2011-03-26 Thread Edgar Gomes Araujo
Hi, I'm running in errors that, I think, is related with functional dependence. But I don't know how to interpret or solve them. I have basically 3 types: Edge, Face and Simplex (Tetrahedron) and I want to combined them in a class type such that: - Edge and Face will produce a convex hull - Fac