如何让玩家跳跃(设定速度)? [英] How to make a player jump (set it's y velocity)?

查看:138
本文介绍了如何让玩家跳跃(设定速度)?的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

鉴于以下情况:

  integralB :: Num a =>行为t a  - >行为ta  - 行为的定积分
eJump :: Event ta - 告诉玩家跳跃
bYAccel = pure 4000 - y加速度
bYVel = integralB bYAccel - y速度
bY = integralB bYVel - y position

如何让玩家跳跃设置它的y速度)当一个跳转事件到达时,你需要能够将一个冲动应用到Y速度为跳跃。从你自己的答案中,你已经想出了一个方法来完成所有跳跃的冲动,并将它们加入到加速度的积分中。



你的加速度也是恒定的。如果你不想让玩家不断下降,你需要这样的东西:

  bYAccel =(ifB空降)4000 0 
airborne = fmap(> 0)bY

ifB :: Behavior t Bool - > a - > a - >行为ta
ifB boolBehavior yes no = fmap(\ bool - > if bool then yes else no)boolBehavior

跳跃高度变化的一个可能原因是您没有在玩家着陆时重置速度。如果你有让玩家在某个位置(如地板)上方的规则,并且在玩家击中地板时以某种方式停止加速,则如果位于地板的方向,则还需要将速度设置为0。 (如果你不是在地板的方向上,它也将它设置为0,玩家永远无法获得速度离开地面。)



导致跳跃高度不稳定的原因是球员落地时的最终速度将接近你申请起跳的冲动。使用你的数字,如果以-5000的速度开始跳跃,并以4800的速度结束,则下一次跳跃将增加-5000的冲量,跳跃到仅为-200的起始速度。这可能有一个300的结束速度,所以下一个跳跃将几乎完整-4700跳。



这是一个完整的工作示例。它使用光泽库进行输入和显示。 gameDefinition 对应于您的问题中引入的组件。 integrateDeltas 相当于您的 integralB ,但会产生冲动的事件,这些冲动很容易在时钟框架中生成光泽,并且易于与其他导致冲动的事件混合使用,例如跳跃。

  { - #LANGUAGE RankNTypes# - } 
模块Main其中

导入Reactive.Banana
导入Reactive.Banana.Frameworks.AddHandler
导入Reactive.Banana.Frameworks

导入数据.IORef
导入合格的Graphics.Gloss.Interface.IO.Game作为光泽

gameDefinition :: GlossGameEvents t - >行为t Gloss.Picture
gameDefinition events = renderBehavior
其中
bY = accumB 0(fmap sumIfPositive yShifts)
yShifts = integrateDeltas bYVel

bYVel = accumB 0 yVelChanges
yVelChanges = apply((ifB airborne)(+)sumIfPositive)yVelShifts
yVelShifts = union(integrateDeltas bYAccel)(fmap(const 3)eJump)

bYAccel =( ifB airborne)(-10)0
airborne = fmap(> 0)bY

eJump = filterE isKeyEvent(事件事件)

integrateDeltas = integrateDeltaByTimeStep(timeStep事件)

renderBehavior =(liftA3渲染)bY bYVel bYAccel
渲染y yVel yAccel =
Gloss.Pictures [
Gloss.Translate 0(20 + y * 100 )(Gloss.Circle 20),
Gloss.Translate(-50)(-20)(readableText(show y)),
Gloss.Translate(-50)(-40)(readableText(sho ),
Gloss.Translate(-50)(-60)(可读文本(显示yAccel))
]
可读文本=(Gloss.Scale 0.1 0.1)。 Gloss.Text


- 工具
sumIfPositive ::(Ord n,Num n)=> n - > n - > n
sumIfPositive x y = max 0(x + y)

ifB :: Behavior t Bool - > a - > a - >行为t a
ifB boolBehavior yes no = fmap(\ bool - > if bool then yes else no)boolBehavior

integrateDeltaByTimeStep ::(Num n)=>事件t n - >行为t n - >事件t
integrateDeltaByTimeStep timeStep衍生物= apply(fmap(*)衍生物)timeStep

isKeyEvent :: Gloss.Event - > Bool
isKeyEvent(Gloss.EventKey _ _ _ _)= True
isKeyEvent _ = False

- 运行它的主循环

main: :IO()
main = do
reactiveGame(Gloss.InWindowReactive Game Example(400,400)(10,10))
Gloss.white
100
gameDefinition

- 活性光泽游戏
data GlossGameEvents t = GlossGameEvents {
event :: Event t Gloss.Event,
timeStep :: Event t Float
}

makeReactiveGameNetwork :: Frameworks t
=> IORef Gloss.Picture
- > AddHandler Gloss.Event
- > AddHandler Float
- > (forall t。GlossGameEvents t - > Behavior t Gloss.Picture)
- > Moment t()
makeReactiveGameNetwork latestFrame glossEvent glossTime game = do
eventEvent< - fromAddHandler glossEvent
timeStepEvent< - fromAddHandler glossTime
let
events = GlossGameEvents {event = eventEvent,timeStep = timeStepEvent}
pictureBehavior =游戏事件
pictureChanges< - 修改pictureBehavior
reactimate(fmap(writeIORef latestFrame)pictureChanges)

reactiveGame :: Gloss。显示
- > Gloss.Color
- > Int
- > (forall t。GlossGameEvents t - > Behavior t Gloss.Picture)
- > IO()
reactiveGame显示颜色步骤game = do
latestFrame< - newIORef Gloss.Blank
(glossEvent,fireGlossEvent)< - newAddHandler
(glossTime,addGlossTime)< - newAddHandler
网络< - 编译(makeReactiveGameNetwork latestFrame glossEvent glossTime游戏)
启动网络
Gloss.playIO
显示
颜色
步骤
(\世界 - > readIORef latestFrame)
(\事件世界 - > fireGlossEvent事件)
(\时间世界 - > addGlossTime时间)

在这个例子中, bY 0,通过积累脉冲,但限制累计值大于0。

速度, bYVel ,积累所有的冲动都是空中的,但只有那些在没有空降的情况下离开地板的冲动。如果您更改

  yVelChanges = apply((ifB airborne)(+)sumIfPositive)yVelShifts 

to

  yVelChanges = fmap(+ )yVelShifts 

它重新创建了不稳定的跳跃错误。



加速度 bYAccel 只在空降时出现。

我使用坐标系统, Y轴向上(与加速度相反)。

最后的代码是一个小型框架,可以将反应式香蕉挂到光泽上。

b $ b

Given the following:

integralB :: Num a => Behavior t a -> Behavior t a -- definite integral of a behaviour
eJump :: Event t a -- tells the player to jump
bYAccel = pure 4000 -- y acceleration
bYVel = integralB bYAccel -- y velocity
bY = integralB bYVel -- y position

How do I make the player jump (probably by setting its y velocity) when a jump event arrives?

解决方案

You'll need to be able to apply an impulse to the Y velocity for the jump. From your own answer, you've come up with a way to do so by summing all the impulses from the jumps and adding them to the integral of the acceleration.

Your acceleration is also constant. If you don't want the player falling constantly, you'd need something like:

bYAccel = (ifB airborne) 4000 0
airborne = fmap (>0) bY

ifB :: Behavior t Bool -> a -> a -> Behavior t a
ifB boolBehavior yes no = fmap (\bool -> if bool then yes else no) boolBehavior

One possible reason the height of your jumps varies is you aren't resetting the velocity when the player lands. If you have rules that hold the player above some position (like the floor), and are somehow stopping acceleration when the player hits the floor, you will also need to set the velocity to 0 if it is in the direction of the floor. (If you also set it to 0 when it's not in the direction of the floor, the player can never get the velocity to leave the ground.)

The reason this would cause erratic jumping heights is that the final velocity when the player lands will be close to the impulse you applied for them to take off. Using your numbers, if a jump started with a velocity of -5000, and ended with a velocity of 4800, the next jump will add an impulse of -5000, taking the jump to a starting velocity of only -200. That might have an ending velocity of 300, so the next jump will be an almost full -4700 jump.

Here's a complete working example. It uses the gloss library for input and display. The gameDefinition corresponds to the components introduced in your question. integrateDeltas is equivalent to your integralB, but produces events that are impulses, which are easy to generate in a clocked framework like gloss, and easy to use mixed with other events that cause impulses, like jumping.

{-# LANGUAGE RankNTypes #-}
module Main where

import Reactive.Banana
import Reactive.Banana.Frameworks.AddHandler
import Reactive.Banana.Frameworks

import Data.IORef
import qualified Graphics.Gloss.Interface.IO.Game as Gloss

gameDefinition :: GlossGameEvents t -> Behavior t Gloss.Picture
gameDefinition events = renderBehavior
    where        
        bY = accumB 0 (fmap sumIfPositive yShifts)
        yShifts = integrateDeltas bYVel

        bYVel = accumB 0 yVelChanges
        yVelChanges = apply ((ifB airborne) (+) sumIfPositive) yVelShifts
        yVelShifts = union (integrateDeltas bYAccel) (fmap (const 3) eJump)

        bYAccel = (ifB airborne) (-10) 0
        airborne = fmap (>0) bY        

        eJump = filterE isKeyEvent (event events)        

        integrateDeltas = integrateDeltaByTimeStep (timeStep events)

        renderBehavior = (liftA3 render) bY bYVel bYAccel 
        render y yVel yAccel =
            Gloss.Pictures [
                Gloss.Translate 0 (20+y*100) (Gloss.Circle 20),
                Gloss.Translate (-50) (-20) (readableText (show y)),
                Gloss.Translate (-50) (-40) (readableText (show yVel)),
                Gloss.Translate (-50) (-60) (readableText (show yAccel))
            ]
        readableText = (Gloss.Scale 0.1 0.1) . Gloss.Text


-- Utilities
sumIfPositive :: (Ord n, Num n) => n -> n -> n
sumIfPositive x y = max 0 (x + y)

ifB :: Behavior t Bool -> a -> a -> Behavior t a
ifB boolBehavior yes no = fmap (\bool -> if bool then yes else no) boolBehavior

integrateDeltaByTimeStep :: (Num n) => Event t n -> Behavior t n -> Event t n
integrateDeltaByTimeStep timeStep derivative = apply (fmap (*) derivative) timeStep

isKeyEvent :: Gloss.Event -> Bool
isKeyEvent (Gloss.EventKey _ _ _ _) = True
isKeyEvent _ = False

-- Main loop to run it

main :: IO ()
main = do   
    reactiveGame (Gloss.InWindow "Reactive Game Example" (400, 400) (10, 10))
        Gloss.white
        100
        gameDefinition

-- Reactive gloss game
data GlossGameEvents t = GlossGameEvents {
    event :: Event t Gloss.Event,
    timeStep :: Event t Float
}

makeReactiveGameNetwork :: Frameworks t
                        => IORef Gloss.Picture
                        -> AddHandler Gloss.Event
                        -> AddHandler Float
                        -> (forall t. GlossGameEvents t -> Behavior t Gloss.Picture)
                        -> Moment t ()
makeReactiveGameNetwork latestFrame glossEvent glossTime game = do
    eventEvent <- fromAddHandler glossEvent
    timeStepEvent <- fromAddHandler glossTime
    let
        events = GlossGameEvents { event = eventEvent, timeStep = timeStepEvent }
        pictureBehavior = game events 
    pictureChanges <- changes pictureBehavior
    reactimate (fmap (writeIORef latestFrame) pictureChanges)       

reactiveGame :: Gloss.Display
             -> Gloss.Color
             -> Int
             -> (forall t. GlossGameEvents t -> Behavior t Gloss.Picture)
             -> IO ()
reactiveGame display color steps game = do
    latestFrame <- newIORef Gloss.Blank
    (glossEvent, fireGlossEvent) <- newAddHandler
    (glossTime, addGlossTime) <- newAddHandler
    network <- compile (makeReactiveGameNetwork latestFrame glossEvent glossTime game)
    actuate network
    Gloss.playIO
        display
        color
        steps
        ()
        (\world -> readIORef latestFrame)
        (\event world -> fireGlossEvent event)
        (\time world -> addGlossTime time)

In this example, bY checks for collision with a floor at 0 by accumulating the impulses, but constraining the accumulated value to be above 0.

The velocity, bYVel, accumulates all impulses while airborne, but only those impulses that are directed away from the floor while not airborne. If you change

yVelChanges = apply ((ifB airborne) (+) sumIfPositive) yVelShifts

to

yVelChanges = fmap (+) yVelShifts

it recreates the erratic jumping bug.

The acceleration, bYAccel, is only present while airborne.

I used a coordinate system with a +Y axis in the up direction (opposite the acceleration).

The code at the end is a small framework to hook reactive-banana up to gloss.

这篇关于如何让玩家跳跃(设定速度)?的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆