<p><font color="#3333ff"><font size="4">Hi! I am getting more problems with compilation. The two files where the problem occurs (a bit more of a general case of the sample of a few hours ago) are:</font></font></p><font color="#3333ff"><font size="4">
<p><br>-------------------------------------------------<br>--------------------Methods.hs-------------------<br>-------------------------------------------------<br>{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances,<br>
  UndecidableInstances, FlexibleContexts, EmptyDataDecls, ScopedTypeVariables,<br>  TypeOperators, TypeSynonymInstances #-}</p>
<p>module Methods where</p>
<p>  import Records<br>  import References</p>
<p>  class Converter a rec_a where convert :: a -&gt; rec_a</p>
<p>  data Method s a b = Method (s -&gt; a -&gt; (b,s))</p>
<p>  (&lt;&lt;-) :: forall rec_a s a b c n . (CNum n, HasField n (b-&gt;(c,a)) (rec_a), Converter a rec_a) =&gt; (Reference s (rec_a)) -&gt; n -&gt; Method s b c<br>  (&lt;&lt;-) r n =<br>    Method(\s -&gt; \(x :: b) -&gt;<br>
              let (v,s&#39;) = getter r s :: (rec_a,s)<br>                  m = v .! n :: (b -&gt; (c,a))<br>                  (y,v&#39;) = m x :: (c, a)<br>                  v&#39;&#39; = convert v&#39; :: rec_a<br>                  ((),s&#39;&#39;) = setter r s&#39; v&#39;&#39;<br>
              in (y,s&#39;&#39;))</p>
<p><br>  (.!!) :: Method s a b -&gt; a -&gt; Reference s b<br>  (Method m) .!! x = from_constant (Constant (\s -&gt; m s x))</p>
<p><br>-------------------------------------------------<br>---------------------Main.hs---------------------<br>-------------------------------------------------<br>{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances,<br>
  UndecidableInstances, FlexibleContexts, EmptyDataDecls, ScopedTypeVariables,<br>  TypeOperators, TypeSynonymInstances #-}</p>
<p>--module Main where</p>
<p>import Records<br>import References<br>import ReferenceMonad<br>import Methods</p>
<p>val = firstLabel<br>incr = nextLabel val</p>
<p>instance Converter RecCounter (Counter RecCounter) where <br>  convert (RecCounter r) = r</p>
<p>type Counter k = (Integer :* (() -&gt; ((),k)) :* EmptyRecord)<br>data RecCounter = RecCounter (Counter RecCounter)</p>
<p>mk_test :: Integer -&gt; RecCounter<br>mk_test i = <br>    RecCounter(    val .= i<br>                .* incr .= (\() -&gt; ((), mk_test (i+1)))<br>                .* EmptyRecord)</p>
<p>RecCounter test&#39; = mk_test 0</p>
<p><br>res2 :: Reference (Counter RecCounter) Integer<br>res2 = do (this &lt;&lt;- incr :: Method (Counter RecCounter) () ()) .!! ()<br>          v &lt;- (this &lt;-- val)<br>          return v</p>
<p>count = fst (getter res2 test&#39;)</p>
<p> </p>
<p>Whenever I try to compile I get the following error:</p>
<p>*Methods&gt; :load Main.hs<br>[1 of 5] Compiling Records          ( Records.hs, interpreted )<br>[2 of 5] Compiling References       ( References.hs, interpreted )<br>[3 of 5] Compiling ReferenceMonad   ( ReferenceMonad.hs, interpreted )<br>
[4 of 5] Compiling Methods          ( Methods.hs, interpreted )<br>[5 of 5] Compiling Main             ( Main.hs, interpreted )</p>
<p>Main.hs:55:11:<br>    No instances for (HasField<br>                        Z (() -&gt; ((), a)) (AddField (() -&gt; ((), RecCounter)) Emp<br>tyRecord),<br>                      Converter a (Counter RecCounter))<br>      arising from a use of `&lt;&lt;-&#39; at Main.hs:55:11-23<br>
    Possible fix:<br>      add an instance declaration for<br>      (HasField<br>         Z (() -&gt; ((), a)) (AddField (() -&gt; ((), RecCounter)) EmptyRecord),<br>       Converter a (Counter RecCounter))<br>    In the first argument of `(.!!)&#39;, namely<br>
        `(this &lt;&lt;- incr :: Method (Counter RecCounter) () ())&#39;<br>    In a stmt of a &#39;do&#39; expression:<br>          (this &lt;&lt;- incr :: Method (Counter RecCounter) () ()) .!! ()<br>    In the expression:<br>
        do (this &lt;&lt;- incr :: Method (Counter RecCounter) () ()) .!! ()<br>         v &lt;- (this &lt;-- val)<br>         return v<br>Failed, modules loaded: Methods, References, Records, ReferenceMonad.<br>*Methods&gt;</p>

<p><br>Any hints?</p>
<p>PS:  just to give some perspective on the code: I am putting together a system for expressing mutable objects through monads. I could provide the rest of my code in case of need :)<br clear="all"></p></font></font><br>
-- <br>Giuseppe Maggiore<br>Ph.D. Student (Languages and Games)<br>Microsoft Student Partner<br>Mobile: +393319040031<br>Office: +390412348444<br><br><br>