Would this be a correct implementation?:

{-# LANGUAGE MultiParamTypeClasses #-}     -- for some reason compiler says to use it ?

import qualified Control.Monad.State.Lazy as Lazy

instance MonadState MyState X where
    get = X Lazy.get
    put s = X $ Lazy.put s


Konstantin

On Thu, Mar 5, 2015 at 4:37 PM, Konstantin Saveljev <konstantin.saveljev@gmail.com> wrote:
I believe Francesco has a point here. I do have "deriving (MonadState MyState)" which is probably causing the problem.

Unfortunately I'm not capable of writing the instance myself. Maybe someone could help me?

My full declaration looks something like this:

    newtype X a = X (StateT MyState (ExceptT String IO) a)
                    deriving (Functor, Applicative, Monad, MonadIO, MonadError String, MonadState MyState)

If I was to remove "MonadState MyState" from the "deriving" section, how would one implement it?


Konstantin

On Thu, Mar 5, 2015 at 4:25 PM, <amindfv@gmail.com> wrote:


El Mar 5, 2015, a las 8:43, Konstantin Saveljev <konstantin.saveljev@gmail.com> escribió:

> Hello,
>
> I'm having some trouble with cyclic dependency.
>
> My simplified version of hierarchy:
>
>     module A where
>
>     import MyState
>
>     data A a = A (StateT MyState IO a) deriving (...)
>
> Now there is a module MyState:
>
>     module MyState where
>
>     import SomeType
>
>     data MyState = MyState { st :: SomeType, ... }
>
> Finally the module that introduces cyclic dependency:
>
>     module SomeType where
>
>     import A
>
>     data SomeType = SomeType { f :: A (), ... }
>
> I have been suggested to move the types into one module and then import it wherever needed. But the problem is that even if I put them into one file those three data types still form a cyclic dependency and compiler throws errors saying "i don't know about this"
>
> So if I have a single module:
>
>     data A a = A (StateT MyState IO a) deriving (...)
>     data MyState = MyState { st :: SomeType, ... }
>     data SomeType = SomeType { f :: A (), ... }
>
> With this setup the compiler is gonna tell us it doesn't know about MyState. And no matter how we shuffle these types within a file we are still getting some "unknowns"
>

Did you try it? It should work fine -- haskell doesn't care about the order of data declarations within a file.

Tom


> How would one approach such a problem?
>
> Best regards,
> Konstantin
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners