1

以下を考えると:

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 速度を設定することによって)。

4

2 に答える 2

2

ジャンプの 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 軸が上方向 (加速度の反対側) の座標系を使用しました。

最後のコードは、リアクティブ バナナをグロスに接続するための小さなフレームワークです。

于 2013-12-19T09:15:25.590 に答える
0

解決しました!これを以前に考えなかったのは少しばかげているように感じますが、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

なぜかジャンプの高さがいつも微妙に違うのですが、それは私のタイミングとは関係ない問題かもしれません。

誰かがより良い質問を共有したい場合に備えて、この質問を回答済みとしてマークしません。

于 2013-12-19T06:10:15.667 に答える