How to solve this using State Monad?

Hello, A very good morning to all. I am a Haskell beginner. And although I have written fairly complicated programs and have understood to some extent the concepts like pattern matching, folds, scans, list comprehensions, but I have not satisfactorily understood the concept of Monads yet. I have partially understood and used the Writer, List and Maybe monads but the State monad completely baffles me. I wanted to write a program for the following problem: A DFA simulator. This I guess is a right candidate for State monad as it mainly deals with state changes. What the program is supposed to do is: ====================== It should read a description of a DFA given as a 5 tuple (q, sigma, delta, q0, finals) where - q: a finite set of states - sigma: a finite set of input symbols called the alphabet - delta: a transition function (delta : Q × S -> Q) - q0: start state (q0 belongs-to Q) - finals: a set of accept states (F belongs-to Q) def taken from wikipediahttp://en.wikipedia.org/wiki/Deterministic_finite_automaton#Formal_definitio... and it should also read an input string (over alphabet sigma) and then it should run the input string on the DFA which it should build from the given description and should output (produce) a list of states through which the DFA has passed as it consumed the input string. You can assume that 'q' the set of state is of integers only. Also you can assume that sigma consist only of single character English alphabets ( ['A'..'Z']). The delta will be given as a list of 3-tuple. You don't need to do file IO. Sample input is following 2-tuple: input = (dfa, input-string) where dfa = ([0,1], ['A','B'], [(0,'A',0), (0,'B',1), (1,'A',1), (1,'B',0) ], 0, [1]) input-string = "AAABBABBAABBBABAAAB" Expected output: output = runDFA input -- output = [0,0,0,1,0,0,1,0,0,0,1,0,1,1,0,0,0,0,1] ====================== I wrote a recursive program to do this without using any monads. I simply send the entire dfa, the input string and its partial result in the recursive calls. How to do this using State Monad? Sorry, I may be a block-head but even after reading many tutorials on monads, I am still confused about the state monad. Either the tutorials give a very complicated example or they don't give a complete example that loads and runs properly in the GHCi . Again sorry to say, but the Random number generation example given in RealWorldHaskell didn't help me either. And yes, I have read Brent Yorgey's article on Monad tutorial fallacy too. So, you Monad gurus over here can consider me a block-head, but let me assure you people that I am a sincere person trying to learn this beautiful but difficult concept. I sincerely hope that a monadic solution (that uses Control.Monad.State ) to the DFA problem I gave, will help me understand the working of State Monad. Please note that I wish your solution to use the Control.Monad.State. Thanks in advance. kak

Hi,
On 28 May 2012 19:49, kak dod
I wrote a recursive program to do this without using any monads. I simply send the entire dfa, the input string and its partial result in the recursive calls.
Can you post your solution so we can modify it to use the state monad? Maybe that will be of some help. -- Ozgur Akgun

Hello,
I didn't have that code with me right then. I was using internet cafe. Here
is my code:
http://hpaste.org/69183
Thanks.
kak
On Tue, May 29, 2012 at 2:09 AM, Ozgur Akgun
Hi,
On 28 May 2012 19:49, kak dod
wrote: I wrote a recursive program to do this without using any monads. I simply send the entire dfa, the input string and its partial result in the recursive calls.
Can you post your solution so we can modify it to use the state monad? Maybe that will be of some help.
-- Ozgur Akgun

Hello there kak,
kak dod
So, you Monad gurus over here can consider me a block-head, but let me assure you people that I am a sincere person trying to learn this beautiful but difficult concept.
no worries. Monads aren't particularly complicated. The common mistake is to try to understand "monads" instead of particular monads. If you understand Maybe, Either, State and Reader, you effectively understand what monads are about. State monads are best understood by looking at their definition: newtype State s a = State (s -> (a, s)) For every type 's' the type 'State s' is a monad, a so-called state monad. It represents a function from a value of type 's' (commonly called the "state") to a tuple of two values, the result and a new value of type 's'. Whenever you have a function of this type: myFunc :: S -> (A, S) you could just as well write it as: myFunc :: State S A They are entirely equivalent, except that the State variant encapsulates the function in a newtype constructor. Now just go ahead and write the Monad instance for the State type yourself. Remember that State is a family of monads, not a monad itself: instance Monad (State s) Now to your actual problem: I doubt that you really want a state monad. As said, a state monad is just the type for functions of the above type. It is well possible to encode DFAs that way, but it will be inconvenient and probably not what you want. I would go for a different approach: There is an arrow that is exactly for this kind of computations: the automaton arrow. Its definition is this: newtype Auto a b = Auto (a -> (b, Auto a b)) It takes an input value of type 'a' and gives a result of type 'b' along with a new version of itself. Here is a simple counter: counter :: Int -> Auto Int Int counter x = Auto (\dx -> (x, counter (x + dx))) In the first instant this automaton returns the argument (x). The next automaton will be counter (x + dx), where dx is the automaton's input. What is useful about the automaton arrow is that it encodes an entirely different idea of state: local state. Every automaton has its own local state over which it has complete control. There is an equivalent way to define the automaton arrow: data Auto a b = forall s. Auto ((a, s) -> (b, s)) You can see how this looks a lot like state monads, but the state is local to the particular automaton. You can then connect automata together using Category, Applicative and/or Arrow combinators. The automaton arrow is implemented in the 'arrows' library. It has a slightly scarier type, because it is an automaton transformer. In that library the type Auto (->) is the automaton arrow. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Again to promote the automaton arrow, Henry's "aha!" DFA in the
automaton arrow:
aha :: Auto Char Char
aha = aha' 0
where
aha' :: Int -> Auto Char Char
aha' s =
Auto $ \input ->
case (s, input) of
(0, 'a') -> ('Y', aha' 1)
(1, 'h') -> ('Y', aha' 2)
(2, 'a') -> ('Y', aha' 3)
(3, '!') -> ('*', pure ' ')
_ -> ('N', aha' 0)
Again the state monad is /not/ suitable for automata. State-based
automata can't be routed/composed, while Auto-based automata can be
routed/composed easily. You can feed the output of the 'aha' automaton
into another automaton, etc. For example you could have these:
-- | Produce a list of outputs forever (cycling).
produce :: [b] -> Auto a b
produce = produce' . cycle
where
produce' (x:xs) = Auto (const (x, produce' xs))
-- | Produce "aha!aha!aha!aha!..."
produceAha :: Auto a Char
produceAha = produce "aha!"
Then you could compose the two easily:
aha . produceAha
I almost feel stupid writing these long explanations, just to see them
getting ignored ultimately. The automaton arrow is one of the most
useful and most underappreciated concepts for state in Haskell.
Greets,
Ertugrul
Ertugrul Söylemez
Now to your actual problem: I doubt that you really want a state monad. As said, a state monad is just the type for functions of the above type. It is well possible to encode DFAs that way, but it will be inconvenient and probably not what you want.
I would go for a different approach: There is an arrow that is exactly for this kind of computations: the automaton arrow. Its definition is this:
newtype Auto a b = Auto (a -> (b, Auto a b))
It takes an input value of type 'a' and gives a result of type 'b' along with a new version of itself. Here is a simple counter:
counter :: Int -> Auto Int Int counter x = Auto (\dx -> (x, counter (x + dx)))
In the first instant this automaton returns the argument (x). The next automaton will be counter (x + dx), where dx is the automaton's input.
What is useful about the automaton arrow is that it encodes an entirely different idea of state: local state. Every automaton has its own local state over which it has complete control. There is an equivalent way to define the automaton arrow:
data Auto a b = forall s. Auto ((a, s) -> (b, s))
You can see how this looks a lot like state monads, but the state is local to the particular automaton. You can then connect automata together using Category, Applicative and/or Arrow combinators.
The automaton arrow is implemented in the 'arrows' library. It has a slightly scarier type, because it is an automaton transformer. In that library the type Auto (->) is the automaton arrow.
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

I hear you Ertugrul ;-) I interpret that kak is struggling to understand the State monad, not find the best solution for a DFA, so telling him about something else which is not the State monad will probably not help him too much at this point... Your propaganda is working on me though ! :-) I haven't looked at the arrows area at all so far, but I'm interested in state handling solutions so I see I need to move it up my reading list! Thanks/ Henry On 30 May 2012, at 23:25, Ertugrul Söylemez wrote:
Again to promote the automaton arrow, Henry's "aha!" DFA in the automaton arrow:
aha :: Auto Char Char aha = aha' 0 where aha' :: Int -> Auto Char Char aha' s = Auto $ \input -> case (s, input) of (0, 'a') -> ('Y', aha' 1) (1, 'h') -> ('Y', aha' 2) (2, 'a') -> ('Y', aha' 3) (3, '!') -> ('*', pure ' ') _ -> ('N', aha' 0)
Again the state monad is /not/ suitable for automata. State-based automata can't be routed/composed, while Auto-based automata can be routed/composed easily. You can feed the output of the 'aha' automaton into another automaton, etc. For example you could have these:
-- | Produce a list of outputs forever (cycling). produce :: [b] -> Auto a b produce = produce' . cycle where produce' (x:xs) = Auto (const (x, produce' xs))
-- | Produce "aha!aha!aha!aha!..." produceAha :: Auto a Char produceAha = produce "aha!"
Then you could compose the two easily:
aha . produceAha
I almost feel stupid writing these long explanations, just to see them getting ignored ultimately. The automaton arrow is one of the most useful and most underappreciated concepts for state in Haskell.
Greets, Ertugrul
Ertugrul Söylemez
wrote: Now to your actual problem: I doubt that you really want a state monad. As said, a state monad is just the type for functions of the above type. It is well possible to encode DFAs that way, but it will be inconvenient and probably not what you want.
I would go for a different approach: There is an arrow that is exactly for this kind of computations: the automaton arrow. Its definition is this:
newtype Auto a b = Auto (a -> (b, Auto a b))
It takes an input value of type 'a' and gives a result of type 'b' along with a new version of itself. Here is a simple counter:
counter :: Int -> Auto Int Int counter x = Auto (\dx -> (x, counter (x + dx)))
In the first instant this automaton returns the argument (x). The next automaton will be counter (x + dx), where dx is the automaton's input.
What is useful about the automaton arrow is that it encodes an entirely different idea of state: local state. Every automaton has its own local state over which it has complete control. There is an equivalent way to define the automaton arrow:
data Auto a b = forall s. Auto ((a, s) -> (b, s))
You can see how this looks a lot like state monads, but the state is local to the particular automaton. You can then connect automata together using Category, Applicative and/or Arrow combinators.
The automaton arrow is implemented in the 'arrows' library. It has a slightly scarier type, because it is an automaton transformer. In that library the type Auto (->) is the automaton arrow.
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hello Ertugrul,
Thank you very much for your patience with a stupid like me. I am going
through your comments, part of it is going parallel but I am getting
something. Sorry for that.
But I am bit confused with the purpose of State Monad now. Is the name
"State Monad" appropriate to this monad?
I mean, if it is appropriate then the State Monad must be useful to model
all types of computations involving state as a dominant part. Am I making a
mistake here? I guess, I am.
Because it seems from what you have said that the State Monad is
appropriate only for some types of computations involving state and not
appropriate for something like DFA which I think is a stateful computation.
What I am trying to do is write a Turing Machine simulator in Haskell? It's
also mainly a state change thing, so if Ertugrul says that State Monad is
not suitable for DFA simulation, it won't be suitable for TM simulation
either.
So, exactly what type of computations involving what type of states are
better handled by the State Monad?
I mean what type of state-computations can be made composible using the
State Monad and what type of state-computations cannot be made composible
using the State Monad? (As you have pointed out automaton cannot be made
composible using the State Monad in an elegant manner.)
Thanks Henry for your example, it has helped me a lot.
On Thu, May 31, 2012 at 6:12 AM, Henry Lockyer
I hear you Ertugrul ;-)
I interpret that kak is struggling to understand the State monad, not find the best solution for a DFA, so telling him about something else which is not the State monad will probably not help him too much at this point...
Your propaganda is working on me though ! :-) I haven't looked at the arrows area at all so far, but I'm interested in state handling solutions so I see I need to move it up my reading list! Thanks/ Henry
On 30 May 2012, at 23:25, Ertugrul Söylemez wrote:
Again to promote the automaton arrow, Henry's "aha!" DFA in the automaton arrow:
aha :: Auto Char Char aha = aha' 0 where aha' :: Int -> Auto Char Char aha' s = Auto $ \input -> case (s, input) of (0, 'a') -> ('Y', aha' 1) (1, 'h') -> ('Y', aha' 2) (2, 'a') -> ('Y', aha' 3) (3, '!') -> ('*', pure ' ') _ -> ('N', aha' 0)
Again the state monad is /not/ suitable for automata. State-based automata can't be routed/composed, while Auto-based automata can be routed/composed easily. You can feed the output of the 'aha' automaton into another automaton, etc. For example you could have these:
-- | Produce a list of outputs forever (cycling). produce :: [b] -> Auto a b produce = produce' . cycle where produce' (x:xs) = Auto (const (x, produce' xs))
-- | Produce "aha!aha!aha!aha!..." produceAha :: Auto a Char produceAha = produce "aha!"
Then you could compose the two easily:
aha . produceAha
I almost feel stupid writing these long explanations, just to see them getting ignored ultimately. The automaton arrow is one of the most useful and most underappreciated concepts for state in Haskell.
Greets, Ertugrul
Ertugrul Söylemez
wrote: Now to your actual problem: I doubt that you really want a state monad. As said, a state monad is just the type for functions of the above type. It is well possible to encode DFAs that way, but it will be inconvenient and probably not what you want.
I would go for a different approach: There is an arrow that is exactly for this kind of computations: the automaton arrow. Its definition is this:
newtype Auto a b = Auto (a -> (b, Auto a b))
It takes an input value of type 'a' and gives a result of type 'b' along with a new version of itself. Here is a simple counter:
counter :: Int -> Auto Int Int counter x = Auto (\dx -> (x, counter (x + dx)))
In the first instant this automaton returns the argument (x). The next automaton will be counter (x + dx), where dx is the automaton's input.
What is useful about the automaton arrow is that it encodes an entirely different idea of state: local state. Every automaton has its own local state over which it has complete control. There is an equivalent way to define the automaton arrow:
data Auto a b = forall s. Auto ((a, s) -> (b, s))
You can see how this looks a lot like state monads, but the state is local to the particular automaton. You can then connect automata together using Category, Applicative and/or Arrow combinators.
The automaton arrow is implemented in the 'arrows' library. It has a slightly scarier type, because it is an automaton transformer. In that library the type Auto (->) is the automaton arrow.
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi kak - ok, my mistake - I interpreted your "candidate for the state monad", and "Please note that I wish your solution to use the Control.Monad.State" too literally. Arrows may point the way forward for you then ;-) I have a suspicion that if the State monad doesn't make sense yet, then Arrows will not be more obvious, they look like a kind of more generalised monadic structure (though I don't understand them myself yet) - but maybe a better fit to your problem will in fact make them clearer for you. Regarding the State monad: I think it may be slightly unfortunate that it gets introduced as THE state monad (I guess Ertugrul may agree here...) and the initial examples, like the favourite random number generation example, do not make it immediately obvious how you might apply it more widely. I certainly experienced a little head-scratching before realising I could simply use things like "charfunc c = state (stateMC c)". Another thing that can cause some initial confusion is the fact that the standard implementation seems to have changed since some of the educational texts were written, so you may find yourself in Hoogle looking at monad transformers before you feel quite ready for them ;-) Also the standard solution does not export the value constructor so, unlike some examples that you may see, you can only use "State" for type definitions and you need to use "state" to create an actual value. I think it is a good idea, as Ertugrul suggested, to write your own state monad instance, and it avoids these 'noise factors' from the library implem. /Henry On 31 May 2012, at 05:29, kak dod wrote:
Hello Ertugrul,
Thank you very much for your patience with a stupid like me. I am going through your comments, part of it is going parallel but I am getting something. Sorry for that.
But I am bit confused with the purpose of State Monad now. Is the name "State Monad" appropriate to this monad? I mean, if it is appropriate then the State Monad must be useful to model all types of computations involving state as a dominant part. Am I making a mistake here? I guess, I am.
Because it seems from what you have said that the State Monad is appropriate only for some types of computations involving state and not appropriate for something like DFA which I think is a stateful computation.
What I am trying to do is write a Turing Machine simulator in Haskell? It's also mainly a state change thing, so if Ertugrul says that State Monad is not suitable for DFA simulation, it won't be suitable for TM simulation either.
So, exactly what type of computations involving what type of states are better handled by the State Monad? I mean what type of state-computations can be made composible using the State Monad and what type of state-computations cannot be made composible using the State Monad? (As you have pointed out automaton cannot be made composible using the State Monad in an elegant manner.)
Thanks Henry for your example, it has helped me a lot.
On Thu, May 31, 2012 at 6:12 AM, Henry Lockyer
wrote: I hear you Ertugrul ;-) I interpret that kak is struggling to understand the State monad, not find the best solution for a DFA, so telling him about something else which is not the State monad will probably not help him too much at this point...
Your propaganda is working on me though ! :-) I haven't looked at the arrows area at all so far, but I'm interested in state handling solutions so I see I need to move it up my reading list! Thanks/ Henry
On 30 May 2012, at 23:25, Ertugrul Söylemez wrote:
Again to promote the automaton arrow, Henry's "aha!" DFA in the automaton arrow:
aha :: Auto Char Char aha = aha' 0 where aha' :: Int -> Auto Char Char aha' s = Auto $ \input -> case (s, input) of (0, 'a') -> ('Y', aha' 1) (1, 'h') -> ('Y', aha' 2) (2, 'a') -> ('Y', aha' 3) (3, '!') -> ('*', pure ' ') _ -> ('N', aha' 0)
Again the state monad is /not/ suitable for automata. State-based automata can't be routed/composed, while Auto-based automata can be routed/composed easily. You can feed the output of the 'aha' automaton into another automaton, etc. For example you could have these:
-- | Produce a list of outputs forever (cycling). produce :: [b] -> Auto a b produce = produce' . cycle where produce' (x:xs) = Auto (const (x, produce' xs))
-- | Produce "aha!aha!aha!aha!..." produceAha :: Auto a Char produceAha = produce "aha!"
Then you could compose the two easily:
aha . produceAha
I almost feel stupid writing these long explanations, just to see them getting ignored ultimately. The automaton arrow is one of the most useful and most underappreciated concepts for state in Haskell.
Greets, Ertugrul
Ertugrul Söylemez
wrote: Now to your actual problem: I doubt that you really want a state monad. As said, a state monad is just the type for functions of the above type. It is well possible to encode DFAs that way, but it will be inconvenient and probably not what you want.
I would go for a different approach: There is an arrow that is exactly for this kind of computations: the automaton arrow. Its definition is this:
newtype Auto a b = Auto (a -> (b, Auto a b))
It takes an input value of type 'a' and gives a result of type 'b' along with a new version of itself. Here is a simple counter:
counter :: Int -> Auto Int Int counter x = Auto (\dx -> (x, counter (x + dx)))
In the first instant this automaton returns the argument (x). The next automaton will be counter (x + dx), where dx is the automaton's input.
What is useful about the automaton arrow is that it encodes an entirely different idea of state: local state. Every automaton has its own local state over which it has complete control. There is an equivalent way to define the automaton arrow:
data Auto a b = forall s. Auto ((a, s) -> (b, s))
You can see how this looks a lot like state monads, but the state is local to the particular automaton. You can then connect automata together using Category, Applicative and/or Arrow combinators.
The automaton arrow is implemented in the 'arrows' library. It has a slightly scarier type, because it is an automaton transformer. In that library the type Auto (->) is the automaton arrow.
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

kak dod
Thank you very much for your patience with a stupid like me. I am going through your comments, part of it is going parallel but I am getting something. Sorry for that.
Sorry, I didn't imply that anyone were stupid. There is a difference between unexperienced and stupid. =)
But I am bit confused with the purpose of State Monad now. Is the name "State Monad" appropriate to this monad? I mean, if it is appropriate then the State Monad must be useful to model all types of computations involving state as a dominant part. Am I making a mistake here? I guess, I am.
Yes, you are mistaken. State monads (there are infinitely many of them (see my original answer)) really model functions of this type: S -> (A, S) Those are functions that take a value of type S (which we call the state) and give a value of type A as well as a value of type S. You can interpret this as modifying state, but in reality it's just an implicit argument and an implicit result of the same type. In fact the more experienced you get in Haskell the less compelled you will be to use a state monad.
Because it seems from what you have said that the State Monad is appropriate only for some types of computations involving state and not appropriate for something like DFA which I think is a stateful computation.
What I am trying to do is write a Turing Machine simulator in Haskell? It's also mainly a state change thing, so if Ertugrul says that State Monad is not suitable for DFA simulation, it won't be suitable for TM simulation either.
You can of course model your DFA as a function of the following type: dfa :: DfaState -> (DfaOutput, DfaState) or equivalently (they are really the same thing): dfa' :: State DfaState DfaOutput My point is: It's not very useful. The problem of the state monad is a very fundamental one. As soon as your automaton is parametric it becomes a function: dfaWith :: DfaInput -> State DfaState DfaOutput Functions in Haskell are opaque. For every composition of automata you would have to write an individual loop, because you would have to force the two individual states to be combined somehow. This gets more inconvenient as your automaton library grows. To allow composition state must be local and the input type must be explicit. This is exactly what the automaton arrow does: dfa :: Auto DfaInput DfaOutput You will notice that the state type is gone. It is now local to 'dfa' and hidden from outside. This is how you would make a smart constructor for Turing machines: turing :: TuringMachine i o -> Auto i o This translation is pretty straightforward.
So, exactly what type of computations involving what type of states are better handled by the State Monad? I mean what type of state-computations can be made composible using the State Monad and what type of state-computations cannot be made composible using the State Monad? (As you have pointed out automaton cannot be made composible using the State Monad in an elegant manner.)
When you have some kind of application/algorithm argument that only very
deep functions use and sometimes update. State monads save you from
having to pass around this argument and extract the result explicitly
all the time. Again this is the full definition of state monads:
newtype State s a = State (s -> (a, s))
There is nothing magic going on. Computations in a state monad are just
functions from 's' to '(a, s'). And there is a simple proof that the
two are equivalent:
runState :: State s a -> (s -> (a, s))
state :: (s -> (a, s)) -> State s a
So there is a one-to-one mapping between the two.
Greets,
Ertugrul
--
Key-ID: E5DD8D11 "Ertugrul Soeylemez

Ertugrul Söylemez
I almost feel stupid writing these long explanations, just to see them getting ignored ultimately. The automaton arrow is one of the most useful and most underappreciated concepts for state in Haskell.
While I'm not sure I have a need for it right now, I definitely haven't ignored this exchange---I've read the individual emails, and a link to the archive is filed away for future use. So it's been very helpful, even if those being helped aren't participating per se. Mike.

A 31/05/2012, às 16:25, Michael Alan Dorman escreveu:
Ertugrul Söylemez
writes: I almost feel stupid writing these long explanations, just to see them getting ignored ultimately. The automaton arrow is one of the most useful and most underappreciated concepts for state in Haskell.
While I'm not sure I have a need for it right now, I definitely haven't ignored this exchange---I've read the individual emails, and a link to the archive is filed away for future use.
So it's been very helpful, even if those being helped aren't participating per se.
+1 Because of those posts I spent my morning reading about arrows which seems a quite interesting concept, although couldn’t yet see what is best for ( I would be curious to learn it in order to try out Yampa). I have to say that the resources I found to learn about arrows on the net were a bit disorganized. This page is really well done http://en.wikibooks.org/wiki/Haskell/Understanding_arrows but then because I don’t know much about parsers I couldn’t really progress through the second half. best, Miguel Negrão

Miguel Negrao
Because of those posts I spent my morning reading about arrows which seems a quite interesting concept, although couldn’t yet see what is best for ( I would be curious to learn it in order to try out Yampa). I have to say that the resources I found to learn about arrows on the net were a bit disorganized. This page is really well done http://en.wikibooks.org/wiki/Haskell/Understanding_arrows but then because I don’t know much about parsers I couldn’t really progress through the second half.
I have started an arrow tutorial which many people found easy to follow. It's not finished yet, but since so many people found it useful I'm sharing that unfinished tutorial: http://ertes.de/new/tutorials/arrows.html It answers the most important questions: What? Why? How? To some extent it also answers: When? But I have to work on that question. The basics of the automaton arrow are covered, but when I find time I will extend the tutorial to cover Auto in full. Finally I also intend to cover a powerful generalization of Auto: the wire arrow, which is the basis of the Netwire AFRP library. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Thu, May 31, 2012 at 9:48 PM, Ertugrul Söylemez
I have started an arrow tutorial which many people found easy to follow. It's not finished yet, but since so many people found it useful I'm sharing that unfinished tutorial:
http://ertes.de/new/tutorials/arrows.html
It answers the most important questions: What? Why? How? To some extent it also answers: When? But I have to work on that question.
Hi Ertugrul, As usual this is useful and I'll be studying it in more detail. For now a general question: What do you think of *teaching* Haskell replacing monads with arrows in the early introduction? Rusi

Rustom Mody
I have started an arrow tutorial which many people found easy to follow. It's not finished yet, but since so many people found it useful I'm sharing that unfinished tutorial:
http://ertes.de/new/tutorials/arrows.html
It answers the most important questions: What? Why? How? To some extent it also answers: When? But I have to work on that question.
As usual this is useful and I'll be studying it in more detail. For now a general question: What do you think of *teaching* Haskell replacing monads with arrows in the early introduction?
According to my experience the same rule that applies to monads also
applies to arrows. In other words: If you can teach monads, you likely
also can teach arrows. If you can't teach monads, don't try to teach
arrows either.
My current position is that understanding applicative functors and
monads makes it much easier to learn arrows. But there is also strong
evidence that teaching arrows first might be useful, building on the
correspondence between Category+Applicative and Arrow. I have not
tried this though.
About my approach to teaching monads there has been a discussion on
Reddit recently:
http://www.haskell.org/pipermail/haskell-cafe/2012-May/101338.html
http://www.reddit.com/r/haskell/comments/u04vp/building_intuition_for_monads...
Greets,
Ertugrul
--
Key-ID: E5DD8D11 "Ertugrul Soeylemez

Hello, I find this whole discussion very much helpful. Ertugrul said: Monads, while being less general, are more expressive.
This statement is rather counter-intuitive for me.
Here is another statement regarding generality and expressiveness:
If we consider DFA and PDA, for instance, PDA is more general and more
expressive than DFA.
Can we say that because PDA is more general than DFA, PDA is more
expressive than DFA.
As per the normal understanding the more general a machine becomes, the
more expressive it is.
So, in what exact sense are you using the terms "general" and "expressive"
w.r.t. Monads and Arrows?
Another thing:
- Is it because Monads are more expressive they are more difficult to
compose (as is the case of the DFA automaton) ?
- Is it because Arrows are less expressive they are easier to compose ?
But then, a more general thing will make it more difficult for us to make
it composible in a yet larger scheme of things.
Am I missing something here?
Thanks and regards,
-Damodar Kulkarni
On Sat, Jun 2, 2012 at 5:32 PM, Ertugrul Söylemez
Rustom Mody
wrote: I have started an arrow tutorial which many people found easy to follow. It's not finished yet, but since so many people found it useful I'm sharing that unfinished tutorial:
http://ertes.de/new/tutorials/arrows.html
It answers the most important questions: What? Why? How? To some extent it also answers: When? But I have to work on that question.
As usual this is useful and I'll be studying it in more detail. For now a general question: What do you think of *teaching* Haskell replacing monads with arrows in the early introduction?
According to my experience the same rule that applies to monads also applies to arrows. In other words: If you can teach monads, you likely also can teach arrows. If you can't teach monads, don't try to teach arrows either.
My current position is that understanding applicative functors and monads makes it much easier to learn arrows. But there is also strong evidence that teaching arrows first might be useful, building on the correspondence between Category+Applicative and Arrow. I have not tried this though.
About my approach to teaching monads there has been a discussion on Reddit recently:
http://www.haskell.org/pipermail/haskell-cafe/2012-May/101338.html < http://www.reddit.com/r/haskell/comments/u04vp/building_intuition_for_monads...
Greets, Ertugrul
-- Key-ID: E5DD8D11 "Ertugrul Soeylemez
" FPrint: BD28 3E3F BE63 BADD 4157 9134 D56A 37FA E5DD 8D11 Keysrv: hkp://subkeys.pgp.net/ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

A 31/05/2012, às 17:18, Ertugrul Söylemez escreveu:
Miguel Negrao
wrote: Because of those posts I spent my morning reading about arrows which seems a quite interesting concept, although couldn’t yet see what is best for ( I would be curious to learn it in order to try out Yampa). I have to say that the resources I found to learn about arrows on the net were a bit disorganized. This page is really well done http://en.wikibooks.org/wiki/Haskell/Understanding_arrows but then because I don’t know much about parsers I couldn’t really progress through the second half.
I have started an arrow tutorial which many people found easy to follow. It's not finished yet, but since so many people found it useful I'm sharing that unfinished tutorial:
http://ertes.de/new/tutorials/arrows.html
It answers the most important questions: What? Why? How? To some extent it also answers: When? But I have to work on that question. The basics of the automaton arrow are covered, but when I find time I will extend the tutorial to cover Auto in full. Finally I also intend to cover a powerful generalization of Auto: the wire arrow, which is the basis of the Netwire AFRP library.
I found your tutorial very enlightening. I think I kind of got more or less the main idea, but I need to try some code to get a feel for it. I mostly program audio related stuff and arrows seem perfect for defining audio synthesis (I already saw some attempts at this with Yampa). I see a lot of similarities between arrows and the Faust audio synthesis languages (perhaps it’s the same core idea ?) http://faust.grame.fr/. best, Miguel Negrão

Miguel Negrao
I mostly program audio related stuff and arrows seem perfect for defining audio synthesis (I already saw some attempts at this with Yampa).
If what you want to define is a monad, you should make it a monad. Arrows are there because of the limitations of monads. Monads, while being less general, are more expressive. If you find that what you want is an arrow, you usually want to make it an applicative functor as well. Applicative style combined with the Category class gives much more declarative descriptions of the same thing (and usually also with higher performance). This is something I wanted to cover in a later chapter in my tutorial, but yeah -- it's not finished yet. =)
I see a lot of similarities between arrows and the Faust audio synthesis languages (perhaps it’s the same core idea ?) http://faust.grame.fr/.
Yes, that looks like functional reactive programming. You can do that with Netwire for example. In fact the code samples can be translated almost 1:1 to Netwire. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

+ I think I already said it, but, in case it was not clear: Me too. Even as a participating person I feel helped! ;-) I just haven't taken it onboard yet and need that quiet free morning to read more about it... + I think this is clearly identifying the point where the State monad(s) can become confusing at first, in my (limited) experience: "The problem of the state monad is a very fundamental one. As soon as your automaton is parametric it becomes a function: dfaWith :: DfaInput -> State DfaState DfaOutput" But I need more time to assimilate the following "Functions in Haskell are opaque. For every composition of automata you would have to write an individual loop, because you would have to force the two individual states to be combined somehow. This gets more inconvenient as your automaton library grows." best/Henry On 31 May 2012, at 16:46, Miguel Negrao wrote:
A 31/05/2012, às 16:25, Michael Alan Dorman escreveu:
Ertugrul Söylemez
writes: I almost feel stupid writing these long explanations, just to see them getting ignored ultimately. The automaton arrow is one of the most useful and most underappreciated concepts for state in Haskell.
While I'm not sure I have a need for it right now, I definitely haven't ignored this exchange---I've read the individual emails, and a link to the archive is filed away for future use.
So it's been very helpful, even if those being helped aren't participating per se.
+1
Because of those posts I spent my morning reading about arrows which seems a quite interesting concept, although couldn’t yet see what is best for ( I would be curious to learn it in order to try out Yampa). I have to say that the resources I found to learn about arrows on the net were a bit disorganized. This page is really well done http://en.wikibooks.org/wiki/Haskell/Understanding_arrows but then because I don’t know much about parsers I couldn’t really progress through the second half.
best, Miguel Negrão _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi kak, On 28 May 2012, at 19:49, kak dod wrote:
Hello, A very good morning to all.
I am a Haskell beginner. And although I have written fairly complicated programs and have understood to some extent the concepts like pattern matching, folds, scans, list comprehensions, but I have not satisfactorily understood the concept of Monads yet. I have partially understood and used the Writer, List and Maybe monads but the State monad completely baffles me.
I wanted to write a program for the following problem: A DFA simulator. This I guess is a right candidate for State monad as it mainly deals with state changes.
What the program is supposed to do is:
. . .
I wrote a recursive program to do this without using any monads. I simply send the entire dfa, the input string and its partial result in the recursive calls.
How to do this using State Monad?
. . .
Please note that I wish your solution to use the Control.Monad.State.
I coincidentally included something like this in another post I recently made. I have quickly tweaked my example slightly and added a complete alternative example using the State monad below. Both programs now have the same external behaviour. It is a simpler example than the DFA that you are proposing. If I have time I'll look at your specific version of the problem, but I am assuming that your main aim here is to understand the State monad better - rather than the DFA exactly as you have specified it - so perhaps the following simple examples may help a little: --------------------------------------------------- -- -- "aha!" -- -- An exciting game that requires the string "aha!" to -- be entered in order to reach the exit, rewarded with a "*". -- -- A simple state machine. -- -- Version 1 - not using the State monad... -- import System.IO type MyState = Char initstate, exitstate :: MyState initstate = 'a' exitstate = 'z' main = do hSetBuffering stdin NoBuffering -- (just so it responds char by char on the terminal) stateIO initstate stateIO :: MyState -> IO () stateIO s = do c_in <- getChar let (c_out, s') = stateMC c_in s putStrLn $ ' ':c_out:[] -- (newline flushes the output) stateIO s' stateMC :: Char -> MyState -> (Char, MyState) stateMC 'a' 'a' = ('Y', 'b') -- 'Y' for 'Yes' stateMC 'h' 'b' = ('Y', 'c') stateMC 'a' 'c' = ('Y', 'd') stateMC '!' 'd' = ('*', 'z') -- '*' for 'Congratulations' stateMC _ 'z' = (' ', 'z') -- Blank responses once game over stateMC _ _ = ('N', 'a') -- 'N' for 'No' ------------------------------------------------------------ -- -- Version 2 - using the State monad... -- This time it treats the input as one long lazy String of chars -- rather than char-by-char reading as in version 1 -- import System.IO import Control.Monad.State type MyState = Char initstate, exitstate :: MyState initstate = 'a' exitstate = 'z' main = do hSetBuffering stdin NoBuffering interact mystatemachine mystatemachine :: String -> String mystatemachine str = concat $ evalState ( mapM charfunc str ) initstate charfunc :: Char -> State MyState String charfunc c = state $ stateMC' c -- wrap the stateMC' func in the state monad -- compared to the stateMC function in version 1 the only difference here in -- stateMC' is that this is also formatting the output as a string with newline, -- which was done separately in 'stateIO' in version 1 stateMC' :: Char -> MyState -> (String, MyState) stateMC' 'a' 'a' = (" Y\n", 'b') stateMC' 'h' 'b' = (" Y\n", 'c') stateMC' 'a' 'c' = (" Y\n", 'd') stateMC' '!' 'd' = (" *\n", 'z') stateMC' _ 'z' = (" \n", 'z') stateMC' _ _ = (" N\n", 'a') ------------------------------------------------------------- Advantages of using the State monad are not really obvious in this example, but perhaps it will help in clarifying what it is doing. It is just wrapping the stateMC' function in a monadic wrapper so that you can make convenient use of the monadic operations >>= etc. and associated functions like mapM etc. for sequencing state computations. 'evalState' takes the chained sequence of state computations, produced by mapM in this case, feeds the initial value into the beginning of the chain, takes the output from the end (which is a pair ([String], MyState) in this case) throws away the final MyState as we are not interested in it here and keeps the [String] (which is then flattened to a single string with concat). +Thanks to the wonders of laziness it works on it char by char as we go along :-) In less trivial cases it helps keep the clutter of the common state handling away from the specifics of what you are doing, like in the Real World Haskell parser example where it nicely handles the parse state. But I guess you are not asking about advantages/disadvantages, but how the hell it works ;-) I have found it confusing too... /Henry

I should have gone back and cleaned up my original 'Version 1' example so that both examples use exactly the same 'stateMC' function. I have now made this small improvement below FWIW. /Henry On 30 May 2012, at 15:31, Henry Lockyer wrote:
Hi kak,
On 28 May 2012, at 19:49, kak dod wrote:
Hello, A very good morning to all.
I am a Haskell beginner. And although I have written fairly complicated programs and have understood to some extent the concepts like pattern matching, folds, scans, list comprehensions, but I have not satisfactorily understood the concept of Monads yet. I have partially understood and used the Writer, List and Maybe monads but the State monad completely baffles me.
I wanted to write a program for the following problem: A DFA simulator. This I guess is a right candidate for State monad as it mainly deals with state changes.
What the program is supposed to do is:
. . .
I wrote a recursive program to do this without using any monads. I simply send the entire dfa, the input string and its partial result in the recursive calls.
How to do this using State Monad?
. . .
Please note that I wish your solution to use the Control.Monad.State.
I coincidentally included something like this in another post I recently made. I have quickly tweaked my example slightly and added a complete alternative example using the State monad below. Both programs now have the same external behaviour. It is a simpler example than the DFA that you are proposing. If I have time I'll look at your specific version of the problem, but I am assuming that your main aim here is to understand the State monad better - rather than the DFA exactly as you have specified it - so perhaps the following simple examples may help a little:
--------------------------------------------------- -- -- "aha!" -- -- An exciting game that requires the string "aha!" to -- be entered in order to reach the exit, rewarded with a "*". -- -- A simple state machine. -- -- Version 1 - not using the State monad... --
import System.IO
type MyState = Char
initstate, exitstate :: MyState initstate = 'a' exitstate = 'z'
main = do hSetBuffering stdin NoBuffering -- (just so it responds char by char on the terminal) stateIO initstate
stateIO :: MyState -> IO () stateIO s = do c_in <- getChar let (str_out, s') = stateMC' c_in s putStr str_out -- (newline flushes the output) stateIO s'
-- now uses exactly the same stateMC func as in version 2 below... -- ('Y' = Yes, 'N' = No, '*' = congratulations game over, blank responses after game over) stateMC' :: Char -> MyState -> (String, MyState) stateMC' 'a' 'a' = (" Y\n", 'b') stateMC' 'h' 'b' = (" Y\n", 'c') stateMC' 'a' 'c' = (" Y\n", 'd') stateMC' '!' 'd' = (" *\n", 'z') stateMC' _ 'z' = (" \n", 'z') stateMC' _ _ = (" N\n", 'a')
------------------------------------------------------------
-- -- Version 2 - using the State monad... -- This time it treats the input as one long lazy String of chars -- rather than char-by-char reading as in version 1 --
import System.IO import Control.Monad.State
type MyState = Char
initstate, exitstate :: MyState initstate = 'a' exitstate = 'z'
main = do hSetBuffering stdin NoBuffering interact mystatemachine
mystatemachine :: String -> String mystatemachine str = concat $ evalState ( mapM charfunc str ) initstate
charfunc :: Char -> State MyState String charfunc c = state $ stateMC' c -- wrap the stateMC' func in the state monad
stateMC' :: Char -> MyState -> (String, MyState) stateMC' 'a' 'a' = (" Y\n", 'b') stateMC' 'h' 'b' = (" Y\n", 'c') stateMC' 'a' 'c' = (" Y\n", 'd') stateMC' '!' 'd' = (" *\n", 'z') stateMC' _ 'z' = (" \n", 'z') stateMC' _ _ = (" N\n", 'a')
-------------------------------------------------------------
Advantages of using the State monad are not really obvious in this example, but perhaps it will help in clarifying what it is doing. It is just wrapping the stateMC' function in a monadic wrapper so that you can make convenient use of the monadic operations >>= etc. and associated functions like mapM etc. for sequencing state computations. 'evalState' takes the chained sequence of state computations, produced by mapM in this case, feeds the initial value into the beginning of the chain, takes the output from the end (which is a pair ([String], MyState) in this case) throws away the final MyState as we are not interested in it here and keeps the [String] (which is then flattened to a single string with concat). +Thanks to the wonders of laziness it works on it char by char as we go along :-)
In less trivial cases it helps keep the clutter of the common state handling away from the specifics of what you are doing, like in the Real World Haskell parser example where it nicely handles the parse state. But I guess you are not asking about advantages/disadvantages, but how the hell it works ;-) I have found it confusing too... /Henry
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hello Henry, But I guess you are not asking about advantages/disadvantages, but how the
hell it works ;-)
Yes, the first thing I want to know is how it works?
thank you very much for your example. It has helped me a lot to begin with.
You have simplified the general DFA problem to a specific one.
Your example seems more helpful to me, but can you please remove the IO
stuff from your first (non-state monadic) example and repost the same
example again?
More specifically, I want to see a definition like:
mystatemachine :: String -> String
in the first example too.
The IO stuff is adding to my confusion as I am unable to compare the exact
difference between the two examples. I could remove the IO part from the
second example very easily by directly executing the function "mystatemachine"
at the GHCi prompt.
The IO stuff more scarier for me. Till now I have not used any IO in
Haskell. I think, if I cannot use State Monad then I cannot use the more
scarier IO monad.
Thanks again for the help.
kak
On Wed, May 30, 2012 at 8:44 PM, Henry Lockyer
I should have gone back and cleaned up my original 'Version 1' example so that both examples use exactly the same 'stateMC' function. I have now made this small improvement below FWIW. /Henry
On 30 May 2012, at 15:31, Henry Lockyer wrote:
Hi kak,
On 28 May 2012, at 19:49, kak dod wrote:
Hello, A very good morning to all.
I am a Haskell beginner. And although I have written fairly complicated programs and have understood to some extent the concepts like pattern matching, folds, scans, list comprehensions, but I have not satisfactorily understood the concept of Monads yet. I have partially understood and used the Writer, List and Maybe monads but the State monad completely baffles me.
I wanted to write a program for the following problem: A DFA simulator. This I guess is a right candidate for State monad as it mainly deals with state changes.
What the program is supposed to do is:
. . .
I wrote a recursive program to do this without using any monads. I simply send the entire dfa, the input string and its partial result in the recursive calls.
How to do this using State Monad?
. . .
Please note that I wish your solution to use the Control.Monad.State.
I coincidentally included something like this in another post I recently made. I have quickly tweaked my example slightly and added a complete alternative example using the State monad below. Both programs now have the same external behaviour. It is a simpler example than the DFA that you are proposing. If I have time I'll look at your specific version of the problem, but I am assuming that your main aim here is to understand the State monad better - rather than the DFA exactly as you have specified it - so perhaps the following simple examples may help a little:
--------------------------------------------------- -- -- "aha!" -- -- An exciting game that requires the string "aha!" to -- be entered in order to reach the exit, rewarded with a "*". -- -- A simple state machine. -- -- Version 1 - not using the State monad... --
import System.IO
type MyState = Char
initstate, exitstate :: MyState initstate = 'a' exitstate = 'z'
main = do hSetBuffering stdin NoBuffering -- (just so it responds char by char on the terminal) stateIO initstate
stateIO :: MyState -> IO () stateIO s = do c_in <- getChar
let (str_out, s') = stateMC' c_in s putStr str_out -- (newline flushes the output)
stateIO s'
-- now uses exactly the same stateMC func as in version 2 below... -- ('Y' = Yes, 'N' = No, '*' = congratulations game over, blank responses after game over)
stateMC' :: Char -> MyState -> (String, MyState) stateMC' 'a' 'a' = (" Y\n", 'b') stateMC' 'h' 'b' = (" Y\n", 'c') stateMC' 'a' 'c' = (" Y\n", 'd') stateMC' '!' 'd' = (" *\n", 'z') stateMC' _ 'z' = (" \n", 'z') stateMC' _ _ = (" N\n", 'a')
------------------------------------------------------------
-- -- Version 2 - using the State monad... -- This time it treats the input as one long lazy String of chars -- rather than char-by-char reading as in version 1 --
import System.IO import Control.Monad.State
type MyState = Char
initstate, exitstate :: MyState initstate = 'a' exitstate = 'z'
main = do hSetBuffering stdin NoBuffering interact mystatemachine
mystatemachine :: String -> String mystatemachine str = concat $ evalState ( mapM charfunc str ) initstate
charfunc :: Char -> State MyState String charfunc c = state $ stateMC' c -- wrap the stateMC' func in the state monad
stateMC' :: Char -> MyState -> (String, MyState) stateMC' 'a' 'a' = (" Y\n", 'b') stateMC' 'h' 'b' = (" Y\n", 'c') stateMC' 'a' 'c' = (" Y\n", 'd') stateMC' '!' 'd' = (" *\n", 'z') stateMC' _ 'z' = (" \n", 'z') stateMC' _ _ = (" N\n", 'a')
-------------------------------------------------------------
Advantages of using the State monad are not really obvious in this example, but perhaps it will help in clarifying what it is doing. It is just wrapping the stateMC' function in a monadic wrapper so that you can make convenient use of the monadic operations >>= etc. and associated functions like mapM etc. for sequencing state computations. 'evalState' takes the chained sequence of state computations, produced by mapM in this case, feeds the initial value into the beginning of the chain, takes the output from the end (which is a pair ([String], MyState) in this case) throws away the final MyState as we are not interested in it here and keeps the [String] (which is then flattened to a single string with concat). +Thanks to the wonders of laziness it works on it char by char as we go along :-)
In less trivial cases it helps keep the clutter of the common state handling away from the specifics of what you are doing, like in the Real World Haskell parser example where it nicely handles the parse state. But I guess you are not asking about advantages/disadvantages, but how the hell it works ;-) I have found it confusing too... /Henry
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

hi kak On 30 May 2012, at 20:17, kak dod wrote:
. . . can you please remove the IO stuff from your first (non-state monadic) example and repost the same example again?
Sure. Here it is, with an essentially similar recursive design in the new non-IO, non-State-monad option. See if it makes any more sense.. br/ Henry -- -- Version 3 - containg two alternative "String -> String" solutions: -- 1) "ahaVanilla" does not use the State monad -- 2) "ahaStMonad" (was 'mystatemachine'in version 2) -- -- the substring "YYY*" followed by spaces (0+) will be found -- in the response string at the position corresponding to the first -- occurrence of substring "aha!" in the input string -- import Control.Monad.State type MyState = Char initstate, exitstate :: MyState initstate = 'a' exitstate = 'z' ahaVanilla :: String -> String ahaVanilla str = vanilla initstate str where vanilla _ [] = [] vanilla state (c:cs) = let (responsechar, nextstate) = stateMC c state in responsechar:( vanilla nextstate cs ) ahaStMonad :: String -> String ahaStMonad str = evalState ( mapM charfunc str ) initstate where charfunc :: Char -> State MyState Char charfunc c = state (stateMC c) stateMC :: Char -> MyState -> (Char, MyState) stateMC 'a' 'a' = ('Y', 'b') stateMC 'h' 'b' = ('Y', 'c') stateMC 'a' 'c' = ('Y', 'd') stateMC '!' 'd' = ('*', 'z') stateMC _ 'z' = (' ', 'z') stateMC _ _ = ('N', 'a')
participants (8)
-
damodar kulkarni
-
Ertugrul Söylemez
-
Henry Lockyer
-
kak dod
-
Michael Alan Dorman
-
Miguel Negrao
-
Ozgur Akgun
-
Rustom Mody