[Haskell-beginners] How to solve this using State Monad?
Henry Lockyer
henry.lockyer at ntlworld.com
Thu May 31 02:42:18 CEST 2012
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 <es at 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
More information about the Beginners
mailing list