[Haskell-cafe] Animas/Yampa - Using Zip as a Routing Function in a Parallel Switch with Feedback

M. George Hansen technopolitica at gmail.com
Mon Sep 19 22:25:20 CEST 2011


Greetings,

I've been playing around with functional reactive programming using
Animas/Yampa and ran into a strange situation. I'm using a parallel
switch to route input to a collection of signal functions and using
the output as feedback (to simulate state). Everything works as
expected until I attempt to use zip as a routing function (i.e. pair
each element of input with a signal function). Using zip as a routing
function causes the program to enter an infinite loop when it
evaluates the output from the parallel switch.

Here is a minimal program that fails to terminate when using zip as a
routing function:
-----------------------------------------------------------------------------------------
{-# LANGUAGE Arrows #-}

module LoopingTest
    (
    )
where

import Control.Arrow
import FRP.Animas

main
    = embed (process []) ([42], [])

process
    :: [Activity]
    -> SF [InputEvent] SystemOutput
process activities
    = proc inputEvents -> do
        rec
            let senses = map (\state -> (inputEvents, state)) states
            states <- par route activities -< senses
        returnA -< states

route
    :: [Sense]
    -> [sf]
    -> [(Sense, sf)]
-- route a sfs = fmap (\sf -> (head a, sf)) sfs
route = zip

type Activity = SF Sense State
type InputEvent = Integer
type State = [Integer]
type Sense = ([InputEvent], State)
type SystemInput = ([InputEvent], [State])
type SystemOutput = [State]
-----------------------------------------------------------------------------------------

If you run the main function as-is the program will run forever, but
if you change the route function to use the commented definition
instead of zip the program terminates normally.

I simply cannot wrap my brain around this issue - zip normally works
just fine with infinite lists as long as one of the lists is finite,
and in this case the number of Activity signal functions is known at
compile time to be finite. I can't find anything conceptually wrong
with using zip as a routing function either. If anyone has any
thoughts I would be very grateful.

-- 
  M. George Hansen
  technopolitica at gmail.com



More information about the Haskell-Cafe mailing list