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? (Ertugrul S?ylemez)
   2. Re:  How to solve this using State Monad? (Henry Lockyer)
   3. Re:  How to solve this using State Monad? (Henry Lockyer)
   4. Re:  How to solve this using State Monad? (kak dod)


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

Message: 1
Date: Thu, 31 May 2012 00:25:38 +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: <20120531002538.17148...@tritium.streitmacht.eu>
Content-Type: text/plain; charset="utf-8"

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/
-------------- 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/298652d8/attachment-0001.pgp>

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

Message: 2
Date: Thu, 31 May 2012 01:24:08 +0100
From: Henry Lockyer <henry.lock...@ntlworld.com>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: <9ad6a844-7f7c-4044-8821-bd16e77e5...@ntlworld.com>
Content-Type: text/plain; charset=us-ascii

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




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

Message: 3
Date: Thu, 31 May 2012 01:42:18 +0100
From: Henry Lockyer <henry.lock...@ntlworld.com>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Cc: Ertugrul S?ylemez <e...@ertes.de>
Message-ID: <591b8d4c-b390-40f6-aedb-b0944583c...@ntlworld.com>
Content-Type: text/plain; charset=iso-8859-1

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




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

Message: 4
Date: Thu, 31 May 2012 09:59:21 +0530
From: kak dod <kak.dod2...@gmail.com>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: Henry Lockyer <henry.lock...@ntlworld.com>
Cc: beginners@haskell.org, Ertugrul S?ylemez <e...@ertes.de>
Message-ID:
        <CAJ4=wNHQOAKdKsRyd1p=CEUyaxMRGaCUs54Fwg=a7ygm-jz...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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/92321df6/attachment.htm>

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

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


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

Reply via email to