[Haskell-cafe] Netwire, keyboard events, and games

Kata Recurse lightquake at amateurtopologist.com
Sun Feb 17 00:27:46 CET 2013


On Feb 16, 2013, at 18:14, "Ertugrul Söylemez" <es at ertes.de> wrote:

> Patrick Hurst <lightquake at amateurtopologist.com> wrote:
>
>> I'm using netwire to build a game; one of the things the player can do
>> is move around using WASD. I want to use key *events* as the 'basis'
>> of my wires, not the entire state vector of the keyboard so that, for
>> example, a press event on D increments the velocity by (200, 0) and a
>> release event decrements it by that much. However, this has the
>> problem that I can't actually get the velocity unless I have an event
>> to feed into the wires, which means I can only update the screen when
>> the user presses or releases a key. While this might make for
>> interesting gameplay, it's not what I want.
>>
>> is the right thing to do to make the input something like a Maybe
>> KeyEvent instead, and pass in Nothing whenever I want to get output
>> without an event for, e.g., a render?
>
> That highly depends on how you want to process the keys.  For real-time
> games you probably want continuous "key held" events instead of
> instantaneous "key down" and "key up" events.  The nicest way here is to
> use a reader monad below the wire with a set of currently pressed keys:
>
>    data GameState =
>        GameState {
>          gsKeyDown :: Set Key
>          {- ... -}
>        }
>
>    type GameWire = WireM (Reader GameState)
>
> That way you can write your event wires like identity wires, which makes
> using them much more convenient.  Here is one way to write such an event
> wire:
>
>    keyDown :: Key -> GameWire a a
>    keyDown key =
>        mkFixM $ \_ x -> do
>            pressed <- asks (S.member key . gsKeyDown)
>            return (if pressed then Right x else Left mempty)
>
> This wire acts like the identity wire when the key is pressed and
> inhibits otherwise.  From such a wire you can easily construct a
> velocity wire for one direction:
>
>    direction :: Key -> Double -> GameWire a Double
>    direction key speed =
>        pure speed . keyDown key <|> 0
>
> When the key is held down, this wire has the 'speed' value, otherwise it
> has the value 0.  A one-dimensional velocity is thus just the sum of two
> of these directions:
>
>    velocity1 :: Key -> Key -> Double -> GameWire a Double
>    velocity1 upKey downKey speed =
>        direction upKey speed +
>        direction downKey (-speed)
>
> A two-dimensional velocity is just a pair of one-dimensional velocities:
>
>    velocity2 speed =
>        velocity1 W S speed &&&
>        velocity1 A D speed
>
> Finally all you need is to turn the velocity into a position.  So
> integrate it:
>
>    position = integral_ (x0, y0) . velocity2 1
>
> I hope this helps.
>
>
> Greets,
> Ertugrul
>
> --
> Not to be or to be and (not to be or to be and (not to be or to be and
> (not to be or to be and ... that is the list monad.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

This is the approach that I currently use; it was pointed out to me
that polling the state of the keys on every input is considered bad
practice since it means that key clicks that happen in between physics
updates don't get registered at all, hence why I wanted to use a more
event-driven approach.



More information about the Haskell-Cafe mailing list