Renamed WiimotePlayer to HWiidPlayer
This commit is contained in:
parent
2ff529b0b1
commit
d2be8eb410
3 changed files with 16 additions and 16 deletions
|
@ -14,7 +14,7 @@ data-files: tex/*.png
|
|||
executable: HTanks
|
||||
hs-source-dirs: src
|
||||
main-is: HTanks.hs
|
||||
other-modules: Collision, CPUPlayer, DefaultPlayer, WiimotePlayer, Game, GLDriver, GLX, Level, MainLoop, Paths_htanks, Player, Render, Simulation, Texture, Debris,
|
||||
other-modules: Collision, CPUPlayer, DefaultPlayer, HWiidPlayer, Game, GLDriver, GLX, Level, MainLoop, Paths_htanks, Player, Render, Simulation, Texture, Debris,
|
||||
Tank, Bindings.GLX, Bindings.GLPng
|
||||
--ghc-options: -threaded
|
||||
extra-libraries: glpng
|
||||
|
|
|
@ -7,7 +7,7 @@ import Render
|
|||
import Player
|
||||
import CPUPlayer
|
||||
import DefaultPlayer
|
||||
import WiimotePlayer
|
||||
import HWiidPlayer
|
||||
import Simulation
|
||||
import Tank
|
||||
|
||||
|
@ -27,14 +27,14 @@ import Foreign.C.Types
|
|||
main :: IO ()
|
||||
main = do
|
||||
let theLevel = testLevel
|
||||
wiimotePlayer <- newWiimotePlayer
|
||||
hwiidPlayer <- newHWiidPlayer
|
||||
gl <- initGL $ glxDriver (levelWidth theLevel) (levelHeight theLevel)
|
||||
|
||||
when (initialized gl) $ do
|
||||
currentTime <- getCurrentTime
|
||||
let mainState = MainState {run = True, driver = SomeDriver gl, time = currentTime, players =
|
||||
[ --SomePlayer $ DefaultPlayer S.empty 0 0 False
|
||||
SomePlayer $ wiimotePlayer
|
||||
SomePlayer $ hwiidPlayer
|
||||
, SomePlayer $ CPUPlayer 0
|
||||
], textures = M.empty}
|
||||
gameState = GameState {level = theLevel, tanks = [ Tank 5.0 5.0 0 0 1.5 270 False 3 1 5 1
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
|
||||
module WiimotePlayer ( WiimotePlayer
|
||||
, newWiimotePlayer
|
||||
module HWiidPlayer ( HWiidPlayer
|
||||
, newHWiidPlayer
|
||||
) where
|
||||
|
||||
import Control.Monad
|
||||
|
@ -22,11 +22,11 @@ import Player
|
|||
import Tank
|
||||
|
||||
|
||||
data WiimotePlayer = WiimotePlayer Wiimote WiimoteAccCal [(Float, Float)]
|
||||
data HWiidPlayer = HWiidPlayer Wiimote WiimoteAccCal [(Float, Float)]
|
||||
deriving (Typeable, Show)
|
||||
|
||||
instance Player WiimotePlayer where
|
||||
playerUpdate (WiimotePlayer wiimote cal oldaims) tank = do
|
||||
instance Player HWiidPlayer where
|
||||
playerUpdate (HWiidPlayer wiimote cal oldaims) tank = do
|
||||
state <- getState wiimote
|
||||
messages <- getMesg wiimote
|
||||
|
||||
|
@ -59,10 +59,10 @@ instance Player WiimotePlayer where
|
|||
angle = atan2 my mx
|
||||
moveangle = if move then Just $ fromRational $ round ((angle - (sin $ 8*x)/8)*1000000*180/pi)%1000000 else Nothing
|
||||
when foo $ print state
|
||||
return (WiimotePlayer wiimote cal aims, moveangle, move, aangle, shoot)
|
||||
return (HWiidPlayer wiimote cal aims, moveangle, move, aangle, shoot)
|
||||
|
||||
renderPlayer (WiimotePlayer _ _ []) = return ()
|
||||
renderPlayer (WiimotePlayer _ _ aims) = unsafePreservingMatrix $ do
|
||||
renderPlayer (HWiidPlayer _ _ []) = return ()
|
||||
renderPlayer (HWiidPlayer _ _ aims) = unsafePreservingMatrix $ do
|
||||
let (x, y) = mulV (1/(fromIntegral $ length aims)) $ foldr addV (0, 0) aims
|
||||
|
||||
translate $ Vector3 x y (0 :: GLfloat)
|
||||
|
@ -136,13 +136,13 @@ lengthSqV a = dotV a a
|
|||
lengthV a = sqrt $ lengthSqV a
|
||||
|
||||
|
||||
newWiimotePlayer :: IO WiimotePlayer
|
||||
newWiimotePlayer = do
|
||||
newHWiidPlayer :: IO HWiidPlayer
|
||||
newHWiidPlayer = do
|
||||
wiimote <- open bdAddrAny (flagMesgInterface .|. flagNonblock)
|
||||
when (wiimote == nullWiimote) $ fail "Wiimote error"
|
||||
setReportMode wiimote (reportButtons .|. reportAcc .|. reportIR .|. reportNunchuk)
|
||||
cal <- getAccCal wiimote extNone
|
||||
return $ WiimotePlayer wiimote cal []
|
||||
return $ HWiidPlayer wiimote cal []
|
||||
|
||||
test :: (Bits a) => a -> a -> Bool
|
||||
test field bits = (field .&. bits) == bits
|
Reference in a new issue