[Haskell-cafe] State Monad

Georg Martius mai99dgf at studserv.uni-leipzig.de
Thu Mar 4 11:08:05 EST 2004


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 <tpledger at ihug.co.nz> 
wrote:

> 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
>




More information about the Haskell-Cafe mailing list