Monad Imparative Usage Example

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

kaveh.shahbazian:
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? 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.
Ok, here you go. A state monad on top of IO, storing just your variable. Its even 'initialised' to undefined at the start :) import Control.Monad.State main = execStateT (do f1; f2; put 10) undefined f1 = do let v = 0 put v liftIO $ print v f2 = do v <- get let v' = v + 4 put v' liftIO $ print v' Running: $ runhaskell A.hs 0 4 10 Of course, there are many other ways to do this, too. -- Don

On 8/2/06, Kaveh Shahbazian
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? 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
You're doing IO so I guess the IO monad would be the way to go here. So something like this: import Data.IORef main = do var <- newIORef 0 fun1 var fun2 var writeIORef var 10 val <- readIORef var putStrLn ( "var " ++ show val) fun1 var = do writeIORef var 0 val <- readIORef var print val fun2 var = do modifyIORef var (+4) val <- readIORef var print val Notice that you have to pass the mutable reference around (no globals) and extract its value explicitly whenever you want to use it. You can also use mutable values using the ST monad rather than the IO monad. This allows you to "run" the resulting actions from within purely functional code, whereas there is no way to run an IO action (i.e. you can't convert an IO Int to an Int - once you're in IO you don't get out). /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

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)

Am Mittwoch, 2. August 2006 11:56 schrieb Kaveh Shahbazian:
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? 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
Well, I don't know C#, so maybe I misinterpreted Console.Write, but probably not, so: import Control.Monad.State fun1 :: StateT Int IO () fun1 = do put 0 var <- get lift $ print var fun2 :: StateT Int IO () fun2 = do modify (+4) var <- get lift $ print var mfun :: StateT Int IO () mfun = do fun1 fun2 put 10 var <- get lift $ putStrLn $ "var = " ++ show var main :: IO () main = evalStateT mfun 0 -- since the initial state isn't used, even undefined would do Another possibility would be (using State Int (IO ()) instead of StateT Int IO ()): import Control.Monad.State fun1 = put (0::Int) >> get >>= return . print fun2 = modify (+4) >> get >>= return . print fin = put 10 >> get >>= return . putStrLn . (++) "var = " . show mfun = sequence [fun1, fun2, fin] main = sequence_ $ evalState mfun 0 but I deem the first preferable. Also take a look at monad tutorials, e.g. Jeff Newbern's All About Monads (sorry, I forgot the URL). Cheers, Daniel -- "In My Egotistical Opinion, most people's C programs should be indented six feet downward and covered with dirt." -- Blair P. Houghton

Hello Kaveh, Wednesday, August 2, 2006, 1:56:10 PM, you wrote:
Question : Could anyone show me a sample of using a monad as a statefull variable?
monad is not an "stateful variable", it's the way to organize computations, rule to join them (as the Ring of Supreme Power ;) ). i recommend you to read http://haskell.org/haskellwiki/IO_inside and "all about monads" tutorials -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Wed, 2006-08-02 at 13:26 +0330, 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? 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.
As other people have noted, you probably don't want to to see this code in Haskell. It's possible to translate stateful code in a 1-1 style but that's not really the point. You'll not get much of the advantages of the language if you do that. You can certainly use console IO etc but for your object containing mutable state, well in a functional style you'd simply not do that and solve the problem in a different way. That's why you see the code people have suggested as translations are bigger than the code you started with, because the language is not naturally imperative. So the trick is to solve your problem in Haskell, not translate your imperative solution to Haskell. Duncan

Thanks All
This is about my tries to understand monads and handling state - as
you perfectly know - is one of them. I have understood a little about
monads but that knowledge does not satidfy me. Again Thankyou
On 8/2/06, Duncan Coutts
On Wed, 2006-08-02 at 13:26 +0330, 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? 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.
As other people have noted, you probably don't want to to see this code in Haskell. It's possible to translate stateful code in a 1-1 style but that's not really the point. You'll not get much of the advantages of the language if you do that.
You can certainly use console IO etc but for your object containing mutable state, well in a functional style you'd simply not do that and solve the problem in a different way.
That's why you see the code people have suggested as translations are bigger than the code you started with, because the language is not naturally imperative.
So the trick is to solve your problem in Haskell, not translate your imperative solution to Haskell.
Duncan

Kaveh Shahbazian wrote:
Thanks All This is about my tries to understand monads and handling state - as you perfectly know - is one of them. I have understood a little about monads but that knowledge does not satidfy me. Again Thankyou
There are many tutorials available from the wiki at http://www.haskell.org/haskellwiki/Books_and_tutorials#Using_Monads and http://www.haskell.org/haskellwiki/Monad Another way is to look at the source code for the State monad and StateT monad transformer, then you can see that the mysterious monad is nothing other than a normal data or newtype declaration together with an instance declaration ie: -- from State.hs newtype State s a = S (s -> (a,s)) instance Monad (State s) where return a = S (\s -> (a, s)) S m >>= k = S (\s -> let (a, s1) = m s S n = k a in n s1) So if you want to understand what's going on when you write: do x <- q p a first step is to remove the syntactic sugar to get: q >>= (\x -> p) and then replace the >>= with it's definition for the monad you're using. For example with the State monad, (q) must be some expression which evaluates to something of the form S fq where fq is a function with type s -> (a,s), and similarly, (\x -> p) must have type a ->S ( s -> (a,s)). If we choose names for these values which describe the types we have: q = S s_as p = a_S_s_as so q >>= (\x -> p) === S s_as >>= a_S_s_as === S (\s0 -> let (a1, s1) = s_as s0 S s_a2s2 = a_S_s_as a1 in s_a2s2 s1) If we use State.runState s0 (q >>= (\x -> p)) to execute this composite action, from the source we see that: runState :: s -> State s a -> (a,s) runState s (S m) = m s so runState s0 (q >>= (\x -> p)) === runState s0 (S (\s0 -> let ... in s_a2s2 s1)) === (\s0 -> let ... in s_a2s2 s1) s0 === s_a2s2 s1 === a2s2 -- ie (a2, s2) Anyway I hope I haven't made things more complicated! ;-) The best thing is to just try and work through some examples yourself with pencil and paper and read lots of tutorials until things start clicking into place. Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Brian Hulley wrote:
q >>= (\x -> p) For example with the State monad, (q) must be some expression which evaluates to something of the form S fq where fq is a function with type s -> (a,s), and similarly, (\x -> p) must have type a ->S ( s -> (a,s)). If we choose names for these values which describe the types we have: q = S s_as p = a_S_s_as
Sorry I meant: (\x -> p) = a_S_s_as ('p' and 'q' stand for arbitrary expressions that evaluate to monadic values) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Very Thankyou I am starting to feel it. I think about it as a 'context' that wraps some computations, which are handled by compiler environment (please make me correct if I am wrong). Now I think I need to find out how this 'monads' fit in solving problems. And for that I must go through bigger programs to write. Thanks again

Kaveh Shahbazian wrote:
Very Thankyou I am starting to feel it. I think about it as a 'context' that wraps some computations, which are handled by compiler environment (please make me correct if I am wrong). Now I think I need to find out how this 'monads' fit in solving problems. And for that I must go through bigger programs to write. Thanks again
Hi Kaveh - Yes, monads can be used to wrap computations with a context. With the State monad, S (s -> (a,s)), this context is just a value of type (s) which the monadic ops (return) and (>>=) pass around. It's important to see that there is no special compiler magic here: (>>=) is just a normal higher order function. The only place where there is any special compiler magic (*) is the IO monad, but you can get a good idea of what's going on by imagining it as a kind of state monad as if it was IO (RealWorld -> (a, RealWorld)) where RealWorld is a special compiler-generated record containing all the mutable variables used by your program and all external state provided by the operating system eg the contents of the hard drive etc. I'd suggest a possible path to writing larger Haskell programs is just: 1) Understand State monad 2) Use this to understand IO monad 3) Learn about IORefs 4) Read about monad transformers eg StateT and ReaderT 5) Understand how (lift) works by looking at the source (instances of Trans) 6) Read about MonadIO and liftIO 7) Use (ReaderT AppData IO) where AppData is a record of IORefs to write imperative code where "global mutable state" is now neatly encapsulated in a monad So you'd learn about monads and monad transformers while still staying in the comfort zone of normal imperative programming with "global" mutable variables. Of course this is not all that radical... ;-) I found looking at the source code for the various monads and monad transformers makes things a lot easier to understand than the Haddock docs which only contain the type signatures. BTW I've noticed a slight bug in my explanation in that I fixed the result types of both actions to be the same when they could have had different types so my corrected explanation follows below (apologies for not checking it properly before posting the first time):
For example with the State monad, (q) must be some expression which evaluates to something of the form S fq where fq is a function with type s -> (a,s), and similarly, (\x -> p) must have type a ->S ( s -> (a,s)). If we choose names for these values which describe the types we have:
Actually the above types are not general enough because p and q don't need to use the same result type (a), so I'd like to correct my explanation to the following (State monad assumed throughout): q >>= (\x -> p) means that both q and p are expressions that evaluate to monadic values ie values whose type is of the form S (s -> (a, s)) Different actions can have different result types (ie different a's) but all share the same state type (s) because the type that's the instance of Monad is (State s) So we have: q :: S (s -> (a, s)) (\x -> p) :: a -> S (s -> (b, s)) To make the explanation simpler, we can rename the variables in the definition of >>= to reflect their types:
S m >>= k = S (\s -> let (a, s1) = m s S n = k a in n s1)
S s_as >>= a_S_s_bs = S (\s0 -> let (a, s1) = s_as s0 S s_bs = a_S_s_bs a in s_bs s1) so runState s0 (q >>= \x -> p) === runState s0 (S (\s0 -> let ... in s_bs s1)) === (\s0 -> let ... in s_bs s1) s0 === s_bs s1 === bs2 ie (b, s2) where b::b and s2::s is the new state after executing the composite action. (*) There is also the ST monad but I'd leave that for later. Best regards, Brian -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Ooops - more bugs in my explanation... Brian Hulley wrote:
-- from State.hs newtype State s a = S (s -> (a,s))
I used the source given in ghc-6.4.2\libraries\monads\Monad\State.hs but the version of state monad that comes with the hierarchical libs is in ghc-6.4.2\libraries\mtl\Control\Monad\State.hs - the bits related to the explanation behave in the same way but you might find it interesting to decide which implementation is more readable since mtl uses record syntax and the other version doesn't.
q >>= (\x -> p)
means that both q and p are expressions that evaluate to monadic values ie values whose type is of the form
S (s -> (a, s)) So we have:
q :: S (s -> (a, s)) (\x -> p) :: a -> S (s -> (b, s))
Ooops! I meant: q :: State s a (\x -> p) :: a -> State s b therefore the *value* of q is of the form S (s -> (a,s)) and the value of (\x -> p) is of the form (a -> S(s -> (b, s)))
To make the explanation simpler, we can rename the variables in the definition of >>= to reflect their types:
^^^^^^^^ "to reflect the structure of their values" Apologies for the millions of corrections and re-posts for this explanation - no matter how hard I try to proof read my posts something always slips through... ;-) Regards, Brian.
participants (8)
-
Brian Hulley
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Daniel Fischer
-
dons@cse.unsw.edu.au
-
Duncan Coutts
-
Kaveh Shahbazian
-
Sebastian Sylvan