如何让玩家跳跃(设置它的 y 速度)?



给定以下条件:

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

当跳跃事件到来时,我如何让玩家跳跃(可能是通过设置其y速度)?

您需要能够对跳跃的Y速度施加脉冲。根据你自己的答案,你已经想出了一种方法,将跳跃产生的所有脉冲相加,并将它们加到加速度的积分中。

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

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

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

这会导致跳跃高度不稳定的原因是,玩家落地时的最终速度将接近你为他们起飞施加的脉冲。使用你的数字,如果一次跳跃以-5000的速度开始,以4800的速度结束,下一次跳跃将增加-5000的脉冲,使跳跃的起始速度仅为-200。这可能有一个300的结束速度,所以下一跳将是一个几乎完整的4700跳。

这是一个完整的工作示例。它使用光泽库进行输入和显示。gameDefinition对应于您问题中介绍的组件。integrateDeltas相当于你的integralB,但它产生的事件是脉冲,很容易在光泽等计时框架中生成,也很容易与跳跃等引起脉冲的其他事件混合使用。

{-# 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)

在该示例中,bY通过累积脉冲来检查与0处的地板的碰撞,但将累积值限制在0以上。

速度bYVel在空中积累所有脉冲,但只有那些在不在空中时被引导离开地板的脉冲。如果您更改

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

yVelChanges = fmap (+) yVelShifts

它再现了不稳定的跳跃错误。

加速度bYAccel仅在空中存在。

我使用了一个坐标系,+Y轴在上方向(与加速度相反)。

最后的代码是一个小框架,用来将反应香蕉挂起来以进行光泽处理。

解决了它!我觉得之前没有考虑这个有点傻,但我只是在每个eJump增加一个计数器,并将该计数器添加到bYVel中。

bJumpVel = sumB $ (-5000) <$ eJump
bYVel = (+) <$> bJumpVel <*> integralB bYAccel
-- gives the sum of the events
sumB :: Num a => Event t a -> Behavior t a
sumB e = accumB 0 $ (+) <$> e

出于某种原因,跳跃的高度总是有很大的变化,但这可能与我的时间安排无关。

我不会把这个问题标记为已回答,以防有人想分享一个更好的问题。

最新更新