[reactive] Newbie Difficulty ..

Tom Poliquin poliquin at softcomp.com
Thu Sep 17 20:07:25 EDT 2009


I know that this is an advanced group but
I am hoping someone can give us a little
help ..

[Boring History Begins]

I and one of my students have been excitedly
experimenting with Reactive.

We're not Haskell pros but have written 
lots of Haskell code, including an HopenGL Logo,
a computer architecture simulator, and an 
HopenGL conventional robot wall follower simulator.
 (screenshot and code are available here,
http://www.softcomp.com/haskell/wallfollow/wf02.png
http://www.softcomp.com/haskell/wallfollow/wf01.tar.gz
  )

Our goal is to rewrite the conventional wall follower robot
simulation in Reactive. We're happy to publish it once it's 
working.

Several months ago Jules Bean posted 'stars' (to the group)
a demo of a reactive framework similar to,  but not identical
to Colin's.

Inside 'stars' was a file containing several very simple
reactive examples (very useful to us newbies).
http://www.softcomp.com/haskell/wallfollow/JulesReactiveDemo.hs
Source .. including support libraries (Deus subdirectory) is here,
http://www.softcomp.com/haskell/wallfollow/JulesReactiveDemo.tar.gz

After experimenting with these we wrote a reactive robot
controller which is supposed to wall follow. This controller code
produces a file (this way we didn't have to 
rewrite to GUI portion too) to be input later to 
a visual 'player'.

Unfortunately it just hangs and produces no output.

[Boring History Ends]

Undaunted we stepped back and wrote an extremely
simple thermostat / furnace controller.

This exhibits the same untoward hanging behavior
on a blocking read inside 'runReactor'.

The code for the main program is given far below.

Full code (including the Deus directory, where all of Jules
support code resides) is here,
http://www.softcomp.com/haskell/wallfollow/thermostat.tar.gz
Reactive.hs is where most of the interesting support routines
live, including 'runReactor'


We know Reactive is a bit of the cutting edge
and everyone is busy hacking (in the good sense)
but any help would be greatly appreciated.

Any docs or papers you deem appropriate would
be greatly appreciated also. We've been to the standard
places .. Colin's site, Less Meat .., Reactive Mailing list,
Haskell site, Frob, Fran, Fr _fill-in-the-blank_ etc.

I'm hoping we simply made some silly mistake
cause by our tenuous understanding of Reactive.
Could this be the 'lazy pattern matching' issue?
(An example of this with a server/client example
was given in Gentle Intro to Haskell which wouldn't
work until it was 'primed' by a lazy pattern match.

If it would be more appropriate we can try to convert
it to Colins' style.

Any help greatly appreciated,

Tom


---------  Thermostat / Furnace Controller ---------  


module Main where

import System.IO

-- Jules Reactive

import Deus.Reactive
import Data.Time.Clock
--import Data.Time.Calendar
--import Data.Time.Format


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

constFun :: Double -> UTCTime -> Double
constFun constval trash = constval

constB :: Double -> Behaviour Double
constB value = timeFunction (constFun value)

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

furnaceUpdate :: Behaviour Double -> Event Int -> Behaviour Double
furnaceUpdate furnace ticker  = 
    (switcher (constB 25.0) (fmap constB
                             (accumE 25.0 (snapshotWith
                                           (\watts ticker -> (\temp -> 
temp+(watts/100.0)))
                                           furnace ticker))))

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

controllerUpdate :: Behaviour Double -> Event Int -> Behaviour Double
controllerUpdate temp ticker  = (switcher (constB 0.0)
                                 (fmap constB 
                                  (snapshotWith
                                   (\temp tick -> (600.0 - temp) / 1000.0)
                                   temp ticker)))

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

furnaceMain :: Event Int -> Event (IO ())
furnaceMain ticker =
    let watts = (controllerUpdate temp ticker)
        temp = (furnaceUpdate watts ticker) in
        fmap (\result -> putStrLn $ "Temp -> " ++ show result)
             (snapshotWith (\t tick -> "\n" ++ show t)
              temp
              ticker)

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

----------
-- Main --
----------

main = do

    --hSetBuffering stdin NoBuffering
    --hSetBuffering stdout NoBuffering


    ticker <- timewiseIterate 10000 (+1) 0

    runReactor (furnaceMain ticker)

    putStrLn "Done .."
 


More information about the Reactive mailing list