More strange errors when compiling code

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: ------------------------------------------------- --------------------Methods.hs------------------- ------------------------------------------------- {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, FlexibleContexts, EmptyDataDecls, ScopedTypeVariables, TypeOperators, TypeSynonymInstances #-} module Methods where import Records import References class Converter a rec_a where convert :: a -> rec_a data Method s a b = Method (s -> a -> (b,s)) (<<-) :: forall rec_a s a b c n . (CNum n, HasField n (b->(c,a)) (rec_a), Converter a rec_a) => (Reference s (rec_a)) -> n -> Method s b c (<<-) r n = Method(\s -> \(x :: b) -> let (v,s') = getter r s :: (rec_a,s) m = v .! n :: (b -> (c,a)) (y,v') = m x :: (c, a) v'' = convert v' :: rec_a ((),s'') = setter r s' v'' in (y,s'')) (.!!) :: Method s a b -> a -> Reference s b (Method m) .!! x = from_constant (Constant (\s -> m s x)) ------------------------------------------------- ---------------------Main.hs--------------------- ------------------------------------------------- {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, FlexibleContexts, EmptyDataDecls, ScopedTypeVariables, TypeOperators, TypeSynonymInstances #-} --module Main where import Records import References import ReferenceMonad import Methods val = firstLabel incr = nextLabel val instance Converter RecCounter (Counter RecCounter) where convert (RecCounter r) = r type Counter k = (Integer :* (() -> ((),k)) :* EmptyRecord) data RecCounter = RecCounter (Counter RecCounter) mk_test :: Integer -> RecCounter mk_test i = RecCounter( val .= i .* incr .= (\() -> ((), mk_test (i+1))) .* EmptyRecord) RecCounter test' = mk_test 0 res2 :: Reference (Counter RecCounter) Integer res2 = do (this <<- incr :: Method (Counter RecCounter) () ()) .!! () v <- (this <-- val) return v count = fst (getter res2 test') Whenever I try to compile I get the following error: *Methods> :load Main.hs [1 of 5] Compiling Records ( Records.hs, interpreted ) [2 of 5] Compiling References ( References.hs, interpreted ) [3 of 5] Compiling ReferenceMonad ( ReferenceMonad.hs, interpreted ) [4 of 5] Compiling Methods ( Methods.hs, interpreted ) [5 of 5] Compiling Main ( Main.hs, interpreted ) Main.hs:55:11: No instances for (HasField Z (() -> ((), a)) (AddField (() -> ((), RecCounter)) Emp tyRecord), Converter a (Counter RecCounter)) arising from a use of `<<-' at Main.hs:55:11-23 Possible fix: add an instance declaration for (HasField Z (() -> ((), a)) (AddField (() -> ((), RecCounter)) EmptyRecord), Converter a (Counter RecCounter)) In the first argument of `(.!!)', namely `(this <<- incr :: Method (Counter RecCounter) () ())' In a stmt of a 'do' expression: (this <<- incr :: Method (Counter RecCounter) () ()) .!! () In the expression: do (this <<- incr :: Method (Counter RecCounter) () ()) .!! () v <- (this <-- val) return v Failed, modules loaded: Methods, References, Records, ReferenceMonad. *Methods> Any hints? 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 :) -- Giuseppe Maggiore Ph.D. Student (Languages and Games) Microsoft Student Partner Mobile: +393319040031 Office: +390412348444
participants (1)
-
Giuseppe Maggiore