[Haskell-cafe] Functional dependence nightmare

Edgar Gomes Araujo talktoedgar at gmail.com
Sat Mar 26 22:10:34 CET 2011


@ 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

<http://github.com/EdgarGomes/DeUni>@Daniel: In fact, I've inserted that
context trying to fix the problem but it affected nothing. I'll remove it.

Thank you guys, in advanced, for the collaboration!

Edgar



On 26 March 2011 21:50, Daniel Fischer <daniel.is.fischer at googlemail.com>wrote:

> 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?
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110326/e67f9030/attachment.htm>


More information about the Haskell-Cafe mailing list