Search code examples
haskelllazy-evaluationnetwire

netwire: dealing with laziness(?) in mutually dependent wires


I am trying to make objects bounce off the walls, using mutually dependent velocity and location wires. Simple one-dimentional example looks like this:

{-# LANGUAGE Arrows #-}
import Prelude hiding ((.), id)
import Control.Wire
import FRP.Netwire
import Control.Monad.IO.Class

-- location -> (corrected-location, did-bounce)
-- "reflect" location back behind the border and indicate the bounce
checkW :: (HasTime t s) => Wire s () IO Double (Double, Bool)
checkW = mkSF_ check
  where
  check loc
    | loc < 0   = (-loc,  True)
    | loc > 1   = (2-loc, True)
    | otherwise = (loc,   False)

-- did-bounce -> velocity, initial velocity in the argument
velW :: Double -> Wire s () IO Bool Double
velW iv = mkSFN $ \bounce -> (iv, velW (if bounce then -iv else iv))

-- produce tuple (location, velocity)
locvelW :: (HasTime t s) => Wire s () IO a (Double, Double)
locvelW = proc _ -> do
  rec (loc, bounce) <- (checkW . integral 0.5) -< vel
      vel <- (velW 0.3) -< bounce
  returnA -< (loc, vel)

main :: IO ()
main = testWireM liftIO clockSession_ locvelW

If I run this, after the first bounce velocity starts flipping between negative and positive values every step.

I know that I can "fix" it by signalling the velocity wire to make velocity negative or positive depending on which border I bounced off. It works. But I want to understand why I see this behaviour, I know that flip should only happen once, as I explicitly push the object to the other side of the border. I suspect that laziness plays role here, and maybe a strategically placed seq would make it work "as intended".

I'd like to have an explanation, and suggestion how to fix it without resorting to "brute force" solution.


Solution

  • This behavior is due to a simple logical error in velW. velW isn't changing the velocity when it bounces, it's only changing the initial velocity for the next time the velocity is calculated; they should both change. Here's a correct version.

    -- did-bounce -> velocity, initial velocity in the argument
    velW :: Double -> Wire s e m Bool Double
    velW iv = mkSFN $ \bounce -> let vel = if bounce then -iv else iv in (vel, velW vel)
    

    Laziness can't play a role here. Laziness affects when a computation happens, but it doesn't affect what the computation means. A pure computation is unaffected by side-effects, so its result doesn't depend on when it is evaluated.