[Haskell-cafe] Netwire bouncing ball

Jason Dagit dagitj at gmail.com
Wed Jul 10 23:32:23 CEST 2013


On Wed, Jul 10, 2013 at 2:15 PM, Just <haskell at justnothing.org> wrote:
> Hello,
>
> I'm trying to get a grasp of netwire by implementing a bouncing ball
> simulation and I'm failing.
> The ball starts from the ground with a given velocity and when hitting the
> ground the wire inhibits successfully. Now I'm kinda stuck.

I've never used netwire (although I've used yampa and
recative-banana), so I can't give you help with the code, but maybe I
can help with the concepts.

I think I see what is wrong. You need to keep applying forces to the
ball. Right now, the code says, once the ball falls below a certain
point, stop applying the force (eg., clamp the output of the
integral). Instead, you could apply an upward force at the point of
impact. You can get this from newton's third law (equal and opposite
reaction). The easiest way to see a bounce would be to simply negate
the velocity when you detect a collision with the ground. A more
accurate way might involve some calculations to figure out the
impulse, but then you'll need more things like the mass of the ball.

I hope that helps,
Jason

>
> How can I make the ball bounce?
>
>
> Here is the code:
>
> {-# LANGUAGE Arrows #-}
>
> module Main where
>
> import Control.Wire
> import Prelude hiding ((.), id)
> import Control.Concurrent
>
> type Pos = Double
> type Vel = Double
> type ObjState = (Pos, Vel)
>
> testApp :: Pos -> Vel -> WireP () ObjState
> testApp p0 v0 = proc _ -> do
>     v <- integral_ v0 -< -9.81
>     p <- integral1_ p0 -< v
>     when (>= 0) -< p
>     returnA -< (p, v)
>
> main :: IO ()
> main = loop' (testApp 0 30) clockSession
>     where
>     loop' w' session' = do
>         threadDelay 1000000
>         (mx, w, session) <- stepSessionP w' session' ()
>         case mx of
>             Left ex -> putStrLn ("Inhibited: " ++ show ex)
>             Right x -> putStrLn ("Produced: " ++ show x)
>         loop' w session
>
> Thanks in advance!
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list