[Haskell-cafe] Hopefully simple monad question
Miguel Mitrofanov
miguelimo38 at yandex.ru
Wed Sep 16 06:42:21 EDT 2009
Well, it's almost always better to reuse as much code as possible. But I
don't think "type" is an answer here. I recommend using a "newtype",
enabling "GeneralizedNewtypeDeriving" and deriving as much as possible:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
...
newtype VM a =
VM {runVM :: State VMState a} deriving Monad
or
newtype VMT m a =
VMT {runVMT :: StateT VMState m a}
deriving (Monad, MonadIO, MonadTrans, TransM)
Unfortunately, you can't automatically derive MonadState, since it's a
multi-paremeter type class. You'll have to write down the derivation
yourself.
Gregory Propf wrote:
> I'm playing around with a little program that implements a simple
> virtual machine. I want to use a monad to represent machine state. I
> created a data type for the machine (VM) and a monadic type for the
> monadic computations using it. I declared this an instance of
> MonadState and Monad and created the usual operators. That stuff
> works. My issue is that I want to run some functions in the machine
> monad, call it VMS - "virtual machine w/state" and then pull the
> underlying VM data structure out and print it.
>
> I've read about monad transformers, lift, liftM, liftIO and all these
> instances in the libraries like MonadIO and am rather confused. The
> most sensible conclusion I can reach is that I probably need to create
> my own Transformer monad and define liftIO. Is this where I need to
> go? Also, my VMS monad doesn't really do anything different from the
> State monad except explicitly specify that state is a VM and not a
> generic type. Am I doing too much work creating my own instances here?
> Would a simple "type" statement work?
>
>
>
> ------------------------------------------------------------------------
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list