Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  How to solve this using State Monad? (Henry Lockyer)
   2. Re:  How to solve this using State Monad? (Ertugrul S?ylemez)
   3. Re:  How to solve this using State Monad? (Michael Alan Dorman)


----------------------------------------------------------------------

Message: 1
Date: Thu, 31 May 2012 11:58:47 +0100
From: Henry Lockyer <henry.lock...@ntlworld.com>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: kak dod <kak.dod2...@gmail.com>
Cc: beginners@haskell.org, Ertugrul S?ylemez <e...@ertes.de>
Message-ID: <a38a2cbe-70dd-4832-a021-c44f11574...@ntlworld.com>
Content-Type: text/plain; charset="iso-8859-1"

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 <henry.lock...@ntlworld.com> 
> 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 <e...@ertes.de> 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
> 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120531/c6c7bfbe/attachment-0001.htm>

------------------------------

Message: 2
Date: Thu, 31 May 2012 14:46:35 +0200
From: Ertugrul S?ylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: <20120531144635.31eed...@tritium.streitmacht.eu>
Content-Type: text/plain; charset="us-ascii"

kak dod <kak.dod2...@gmail.com> wrote:

> 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 <e...@ertes.de>"
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120531/ae6cdc6f/attachment-0001.pgp>

------------------------------

Message: 3
Date: Thu, 31 May 2012 11:25:05 -0400
From: Michael Alan Dorman <mdor...@ironicdesign.com>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: <87bol4xtim....@ironicdesign.com>
Content-Type: text/plain; charset=utf-8

Ertugrul S?ylemez <e...@ertes.de> 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.

Mike.



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 47, Issue 33
*****************************************

Reply via email to