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') <- case build1stUnit plane p1 p2 p of
                Just un  -> return (([un], fromList $ getAllSubUnits un)::(SubUnit a)=>([Unit a], SetActiveSubUnits a))
                _        -> return ([]   , empty)
            analyze1stUnit unit afl'
.....


I hope that is right. Does it?

Edgar





On 26 March 2011 21:19, Stephen Tetley <stephen.tetley@gmail.com> wrote:
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, you
want to use scoped type variables so that the local type annotation is
*the same type* type variable.

Best wishes

Stephen

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe