
Hi folks, I have a question to the State Monad or Monads in general - I'am not sure. Lets assume I have functions to transform strings. I can use the State Monad as follows: strTrans :: String -> String strTrans s = s ++ s f :: State String () f = do put "hallo" modify strTrans modify strTrans' ... Up to this point everything is clear. Now I have also functions to map from (a, String) -> (a,String). I could write: modifyT :: ((a, String) -> (a, String)) -> a -> State String a modifyT trans a = do str <- get let (a', str') = trans (a, str) put str' return a' f :: State String () f = do put "hallo" modify strTrans i <- modifyT strIntTrans 4 -- strIntTrans :: (Int, String) -> (Int, String) i' <- modifyT strIntTrans i ... But this is obviously awkward. How can I stick two Monads in each other? I could't figure out how to use StateT. Any help would be appreciated. Thanks! Georg

Am Mittwoch, 3. März 2004 14:44 schrieb Georg Martius:
[...]
Now I have also functions to map from (a, String) -> (a,String). I could write:
modifyT :: ((a, String) -> (a, String)) -> a -> State String a modifyT trans a = do str <- get let (a', str') = trans (a, str) put str' return a'
f :: State String () f = do put "hallo" modify strTrans i <- modifyT strIntTrans 4 -- strIntTrans :: (Int, String) -> (Int, String) i' <- modifyT strIntTrans i ...
But this is obviously awkward. How can I stick two Monads in each other? I could't figure out how to use StateT.
StateT is one solution. See http://www.haskell.org/pipermail/haskell/2004-January/013330.html and the follow-ups (available via the "next message" links). With StateT, modifyT may be written as follows (untested code): modifyT :: ((a, String) -> (a, String)) -> StateT a (State String) () modifyT trans = do str <- liftM get a <- get let (a', str') = trans (a, str) liftM (put str') put a' Alternatively, you can use the ordinary state monad with (a,String) as its state. Then modifyT is just modify.
[...]
Thanks! Georg
Wolfgang

hi, Georg Martius wrote:
Now I have also functions to map from (a, String) -> (a,String). I could write:
modifyT :: ((a, String) -> (a, String)) -> a -> State String a modifyT trans a = do str <- get let (a', str') = trans (a, str) put str' return a'
f :: State String () f = do put "hallo" modify strTrans i <- modifyT strIntTrans 4 -- strIntTrans :: (Int, String) -> (Int, String) i' <- modifyT strIntTrans i ...
But this is obviously awkward. How can I stick two Monads in each other? I could't figure out how to use StateT. Any help would be appreciated.
Thanks! Georg
could you be a little more specific on what you are trying to do? what do you mean by sticking two monads in each other, do you want to have two state componenets, or perhaps work with computations that manipulate state, but can also raise exceptions? -iavor -- ================================================== | Iavor S. Diatchki, Ph.D. student | | Department of Computer Science and Engineering | | School of OGI at OHSU | | http://www.cse.ogi.edu/~diatchki | ==================================================

Georg Martius wrote: [...]
I could write:
modifyT :: ((a, String) -> (a, String)) -> a -> State String a modifyT trans a = do str <- get let (a', str') = trans (a, str) put str' return a'
f :: State String () f = do put "hallo" modify strTrans i <- modifyT strIntTrans 4 -- strIntTrans :: (Int, String) -> (Int, String) i' <- modifyT strIntTrans i ...
But this is obviously awkward.
[...] Hi. People have already replied about the state monad aspect, but there's another small improvement I'd like to suggest. Look at what modifyT does with 'trans' and 'a'. They are always used together. So, how about combining them *outside* the definition of modifyT? modifyT :: (String -> (a, String)) -> State String a modifyT trans = do (a, s) <- gets trans put s return a f = do ... i <- modifyT (strIntTrans 4) -- strIntTrans :: Int -> String -> (Int, String) i' <- modifyT (strIntTrans i) ... Aside: if you rewrite ($) similarly, you get id. Regards, Tom

Hi,
thanks for your suggestion. The thing is, that I don't want to change the
type of my transformation functions.
To answer Iavor's question: I have basically two types of transformation
functions. One StringTransformation (String -> String) and one
transformation with a string and something (e.g. random generator)
((a,String) -> (a,String)). The vast majority of transformation I use are
from the first type. I was looking for a nice way to write this in a the
compact style. I haven't thought about exceptions yet.
My current approach is as follows:
withString :: String -> State String () -> String
withString state monad = execState monad state
withStringAndT :: String -> t -> StateT t (State String) () -> String
withStringAndT state t monad = execState (execStateT monad t) state
modifyT :: ((t, String) -> (t, String))
-> StateT t (State String) ()
modifyT trans
= do s <- lift get
t <- get
let (t', s') = trans (t, s)
lift (put s')
put t'
now I can use either
let str' = withString str $
do modify $ foo_stringtrans
modify $ bar_stringtrans
or
let str' = withStringAndT str (gen) $
do modifyT $ foo_stringgentrans
lift $ modify $ foo_stringtrans
Cheers,
Georg
On Thu, 04 Mar 2004 08:51:04 +1300, Tom Pledger
Georg Martius wrote: [...]
I could write:
modifyT :: ((a, String) -> (a, String)) -> a -> State String a modifyT trans a = do str <- get let (a', str') = trans (a, str) put str' return a'
f :: State String () f = do put "hallo" modify strTrans i <- modifyT strIntTrans 4 -- strIntTrans :: (Int, String) -> (Int, String) i' <- modifyT strIntTrans i ...
But this is obviously awkward.
[...]
Hi.
People have already replied about the state monad aspect, but there's another small improvement I'd like to suggest.
Look at what modifyT does with 'trans' and 'a'. They are always used together. So, how about combining them *outside* the definition of modifyT?
modifyT :: (String -> (a, String)) -> State String a modifyT trans = do (a, s) <- gets trans put s return a f = do ... i <- modifyT (strIntTrans 4) -- strIntTrans :: Int -> String -> (Int, String) i' <- modifyT (strIntTrans i) ...
Aside: if you rewrite ($) similarly, you get id.
Regards, Tom
participants (4)
-
Georg Martius
-
Iavor S. Diatchki
-
Tom Pledger
-
Wolfgang Jeltsch