[Haskell-beginners] State and GUI's / external interfaces / events

Henry Lockyer henry.lockyer at ntlworld.com
Tue May 29 02:15:13 CEST 2012


Hi all,
I'm trying to straighten out my basic understanding around state-based IO handling in Haskell.

I've been reading around in several places but it hasn't clicked yet, and the input buffer is now cluttered with 
new things to assimilate ;-)

The basic question is about what ways there are to implement state-based decisions, where an external event of some kind 
results in some Haskell function/s being called depending on the particular event and the current state, then
perhaps some new external action initiated, and new state set.  Basic state machine type of logic.

As a starting point I include down at the bottom of this mail a little example program which implements something 
like this for terminal IO.  The state/logic could be made arbitrarily more complex.
It's a simple 'event loop' that blocks on getChar until a Char is input, with a separate pure event/state query function.

One could also implement the per-Char state-based handling using the State monad by mapping over 
the Char inputs as a string, for example something like:

main = do hSetBuffering stdin NoBuffering
          interact \str -> evalState ( mapM charfunc str ) initstate
            where charfunc :: Char -> State Char Char
                      . . .
I'm not sure how I would implement the exit case if I used this approach for the 'aha!' game below though.

Anyway, a few interrelated questions running out from this general starting point:

1. I've not really played with monad transformers yet, but I  guess one could use monad transformers to 
   make a combined IO/State monad as an alternative to the basic solution down below.  
   Assuming there is no lurking problem with doing that, does it help? 
   (I can't see much advantage, in this case where explicitly manipulating the state at each step is the main activity.)

2. The 'event loop' in IO in the example below drives the state lookup/branching logic, but how can you separate
    the sequential state logic from the polling process?   This is really the nub of my question.
    I'm not familiar with the FFI or the GUI libraries, so with apologies in advance for misunderstanding it all...
     say for example we want to implement a Haskell program that responds to events arriving as external 
     function calls via the FFI where the state-based logic is in Haskell but the events are not polled for, they
     just arrive (for example could be driven by some main loop in external functionality, eg. GUI). 
     We want the Haskell implementation to respond in a sequential state-based manner so that if
     the external events/calls 'a', 'a', 'h' arrive this could produce different responses (to the second and third events)
     compared to the event sequence 'a', 'h', 'a'. 
     How/can you do this in Haskell?
     The events could come from some completely independent and/or uncontrollable sources but we require the
     Haskell program to respond according to arrival sequence.   
     My intuition says that this is not possible if the events arrive simply as independent function calls on an
     external interface, but that they must be collected somehow into a single sequential 
     entity such as a file, list, 'stream' or somesuch and then they can be mapped over or some kind of read loop can 
     pull them off in sequence as in the example below.   But I am probably wrong :)     ?

3. What state/event handling model do the GUI solutions like whhaskell or gtk2hs use? I read that they use callbacks,
    which makes sense, but does it mean that the callbacks must be manipulated (or some associated widget attributes) so as
    to encode the state back into the GUI at every step?  In other words the first 'a' in the above "aah" vs "aha" example
    would have to, as a minimum, initiate a change in the callback/attributes of the 'a' generator so that the second
    'a' will actually be a different 'a' ( 'a2' perhaps) or carry some additional parameter info so that the correct function in the
    receiving Haskell is invoked?  This could be horrible if there are, say, 50 different widgets that could generate the next event
    and they would all have to be updated to reflect each state change.  I feel it must be better than this somehow..  
    So how does it work?   

Any help appreciated.
Thanks/ Henry

--
-- "aha!" 
--
-- An exciting game that requires the string "aha!" to
-- be entered in order to reach the exit.
--

import System.IO

type MyState = Char

initstate, exitstate :: MyState
initstate = 'a'
exitstate = 'z'

main :: IO ()
main = do hSetBuffering stdin NoBuffering
          stateIO initstate
 
stateIO :: MyState -> IO ()
stateIO s = do c_in <- getChar
               let (c_out, s') = stateMC c_in s
               putStrLn $ ' ':c_out:[]
               if s' /= exitstate then stateIO s' 
                                  else putStrLn "Bye..."

stateMC :: Char -> MyState -> (Char, MyState)
stateMC 'a' 'a' = ('Y', 'b')
stateMC 'h' 'b' = ('Y', 'c')
stateMC 'a' 'c' = ('Y', 'd')
stateMC '!' 'd' = ('*', 'z')
stateMC  _   _  = ('N', 'a')




More information about the Beginners mailing list