[Haskell-cafe] Functional dependence nightmare

Daniel Fischer daniel.is.fischer at googlemail.com
Sat Mar 26 21:50:50 CET 2011


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 = 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))

Remove the context, that's given in the signature:

   return (([un], fromList ...) :: ([Unit a], SetActiveSubUnits a))

>                 _        -> return ([]   , empty)
>             analyze1stUnit unit afl'
> .....
> 
> 
> I hope that is right. Does it?
> 



More information about the Haskell-Cafe mailing list