[Haskell-cafe] Monad Imparative Usage Example

Chris Kuklewicz haskell at list.mightyreason.com
Wed Aug 2 06:36:16 EDT 2006


Kaveh Shahbazian wrote:
> Haskell is the most powerfull and interesting "thing" I'v ever
> encountered in IT world. But with an imparative background and lack of
> understanding (because of any thing include that maybe I am not that
> smart) has brought me problems. I know this is an old issue. But
> please help it.
> Question : Could anyone show me a sample of using a monad as a
> statefull variable?

That question is a bit ill-posed.  A monad is a type of interface.  A stateful 
variable would probably be an IORef or a STRef which can be created and used in 
the IO and ST monads, respectively.

> For example see this code in C# :
> //
> public class Test
> {
>    int var;
>    static void Fun1() { var = 0; Console.Write(var); }
>    static void Fun2() { var = var + 4; Console.Write(var); }
>    static void Main() { Fun1(); Fun2(); var = 10; Console.Write("var
> = " + var.ToString()); }
> }
> //
> I want to see this code in haskell.
> Thankyou
> _______________________________________________

Here is one translation:

> module Imp where
> 
> import Data.IORef
> 
> data Test = Test {var :: IORef Int
>                  ,fun1 :: IO ()
>                  ,fun2 :: IO ()
>                  ,testMain :: IO ()
>                  }
> 
> newTest :: IO Test
> newTest = do var <- newIORef 0
>              let fun1 = do writeIORef var 0
>                            print =<< readIORef var
>                  fun2 = do modifyIORef var (+4)
>                            print =<< readIORef var
>                  main = do fun1
>                            fun2
>                            writeIORef var 10
>                            value <- readIORef var
>                            print ("var = "++show value)
>              return Test {var = var
>                          ,fun1 = fun1
>                          ,fun2 = fun2
>                          ,testMain = main}
> 
> main :: IO ()
> main = do
>   test <- newTest
>   fun1 test
>   fun2 test
>   testMain test
>   print =<< readIORef (var test)



More information about the Haskell-Cafe mailing list