
hi haskellers, i have a basic question regarding StateT encapsulating IO and the modify function. my scenario is similar to the following simple code snippet:
import Control.Monad.State
type MyState = StateT Int IO
test = evalStateT foo 0
foo = do modify $ (+) 1 get
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, like in the following, obviously defunct snippet:
test = evalStateT bar 0
bar = do modify $ myAdd 1 get
myAdd :: Int -> Int -> IO Int myAdd x y = do putStr "in myAdd\n" return $ x + y
this fails because (myAdd :: Int -> Int -> IO Int) does not match the required modify argument type (Int -> Int -> Int) for MyState. Couldn't match expected type `Int' against inferred type `IO Int' In the second argument of `($)', namely `myAdd 1' In the expression: modify $ (myAdd 1) In a 'do' expression: modify $ (myAdd 1) is it possible to 'lift' StateT modify into the inner monad (IO in my case)? regards, peter.

bar = do
x <- get
y <- lift $ myAdd 1 x
put y
return y
If you want, you can write something which captures this idiom:
liftModify c = do
x <- get
y <- lift (c x)
put y
and then use that like:
bar = do
liftModify (myAdd 1)
get
On 08/11/06, Peter Steiner
hi haskellers,
i have a basic question regarding StateT encapsulating IO and the modify function.
my scenario is similar to the following simple code snippet:
import Control.Monad.State
type MyState = StateT Int IO
test = evalStateT foo 0
foo = do modify $ (+) 1 get
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, like in the following, obviously defunct snippet:
test = evalStateT bar 0
bar = do modify $ myAdd 1 get
myAdd :: Int -> Int -> IO Int myAdd x y = do putStr "in myAdd\n" return $ x + y
this fails because (myAdd :: Int -> Int -> IO Int) does not match the required modify argument type (Int -> Int -> Int) for MyState.
Couldn't match expected type `Int' against inferred type `IO Int' In the second argument of `($)', namely `myAdd 1' In the expression: modify $ (myAdd 1) In a 'do' expression: modify $ (myAdd 1)
is it possible to 'lift' StateT modify into the inner monad (IO in my case)?
regards, peter. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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 -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 11/8/06, Bulat Ziganshin
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
thanks. i am aware of trace, but the potentially messed up execution order makes it very hard for me to get useful information out of the resulting trace. besides, IO will scale to more elaborate logging mechanisms later on... -- peter

"Peter" == Peter Steiner
writes:
Peter> On 11/8/06, Bulat Ziganshin
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.

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
"Peter" == Peter Steiner
writes: Peter> On 11/8/06, Bulat Ziganshin
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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
wrote: > "Peter" == Peter Steiner
writes: Peter> On 11/8/06, Bulat Ziganshin
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Applying lift outside of modifyM is not a problem. It can seem a bit tricky with the function types around. Try
modifyM $ lift . myAdd 1
instead of
modifyM $ myAdd 1
Cale's should certainly work fine and lead to more concise code for
what you're after. Just thought I'd mention this in case your needs
change.
Good luck,
Nick
On 11/8/06, Peter Steiner
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
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
wrote: >> "Peter" == Peter Steiner
writes: Peter> On 11/8/06, Bulat Ziganshin
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

stupid me, that works and is more flexible than cale's solution. thanks!
On 11/8/06, Nicolas Frisby
Applying lift outside of modifyM is not a problem. It can seem a bit tricky with the function types around. Try
modifyM $ lift . myAdd 1
instead of
modifyM $ myAdd 1
Cale's should certainly work fine and lead to more concise code for what you're after. Just thought I'd mention this in case your needs change.
Good luck, Nick
On 11/8/06, Peter Steiner
wrote: 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
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
wrote: >>> "Peter" == Peter Steiner
writes: Peter> On 11/8/06, Bulat Ziganshin
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 11/8/06, Max Vasin
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?
good question. my initial idea, being lazy, was that IO provides IORefs which might prove useful later on, but then i guess that a cleanly composed monad will behave better in the long term anyways. i have to add that this is my first large haskell project and i do many design decisions on a trial'n'error basis - naturally with a strong tendency to the error side. ;-) -- peter
participants (5)
-
Bulat Ziganshin
-
Cale Gibbard
-
Max Vasin
-
Nicolas Frisby
-
Peter Steiner