[Haskell-cafe] Re: StateT and modify

Peter Steiner pnsteiner at gmail.com
Wed Nov 8 15:05:04 EST 2006


cale's solution worked fine for me (i forgot to cc this list in my response).

i have troubles getting your modifyM to compile, and i do not really
understand how it might without somehow lifting the function into the
inner monad.

> import Control.Monad.State
>
> type MyState = StateT Int IO
>
> test = evalStateT bar 0
>
> modifyM :: (MonadState s m) => (s -> m s) -> m ()
> modifyM f = do
>    s <- get
>    s' <- f s
>    put s'
>
> bar :: MyState Int
> bar = do
>    modifyM $ myAdd 1
>    get
>
> myAdd :: Int -> Int -> IO Int
> myAdd x y = do
>    putStr "in myAdd\n"
>    return $ x + y

fails with:

    Couldn't match `StateT Int IO' against `IO'
      Expected type: StateT Int IO
      Inferred type: IO
    In a 'do' expression: modifyM $ (myAdd 1)
    In the definition of `bar':
        bar = do
                modifyM $ (myAdd 1)
                get

and applying lift is not possible outside of modifyM.
what am i doing wrong?

regards,
peter.

On 11/8/06, Nicolas Frisby <nicolas.frisby at gmail.com> wrote:
> Regardless of what monad is transformed by StateT, I think the OP's
> issue remains.
>
> modify below is straight from Gill's source at
> http://darcs.haskell.org/packages/
>
> modify :: (MonadState s m) => (s -> s) -> m ()
> modify f = do
>         s <- get
>         put (f s)
>
> we could add
>
> modifyM :: (MonadState s m) => (s -> m s) -> m ()
> modifyM f = do
>         s <- get
>         s' <- f s
>        put s'
>
> which I think you could use...
>
> modifyM is just a bit more flexible than Cale's liftModify, I think.
>
> On 11/8/06, Max Vasin <max.vasin at gmail.com> wrote:
> > >>>>> "Peter" == Peter Steiner <pnsteiner at gmail.com> writes:
> >
> > Peter> On 11/8/06, Bulat Ziganshin <bulat.ziganshin at gmail.com> wrote:
> > >> Hello Peter,
> > >>
> > >> Wednesday, November 8, 2006, 1:48:24 PM, you wrote:
> > >>
> > >> > i would like to be able to debug what's happening inside the
> > >> modifier > function. that's why i want to be able to use a
> > >> modifier that's in the > IO monad
> > >>
> > >> for debugging there is 'trace' function which don't needs IO
> > >> monad
> >
> > Peter> thanks. i am aware of trace, but the potentially messed up
> > Peter> execution order makes it very hard for me to get useful
> > Peter> information out of the resulting trace. besides, IO will
> > Peter> scale to more elaborate logging mechanisms later on...
> >
> > If all you want from IO is logging why not just use MonadWriter?
> >
> > --
> > WBR,
> > Max Vasin.
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> _______________________________________________
> 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