This repository has been archived on 2025-03-03. You can view files and clone it, but cannot push or open issues or pull requests.
htanks/src/WiimotePlayer.hs
2010-04-08 16:00:01 +02:00

57 lines
No EOL
3 KiB
Haskell

{-# LANGUAGE DeriveDataTypeable #-}
module WiimotePlayer ( WiimotePlayer(..)
, newWiimotePlayer
) where
import Control.Monad
import Data.Bits
import Data.Ratio ((%))
import Data.Typeable
import HWiid
import Player
data WiimotePlayer = WiimotePlayer Wiimote
deriving (Typeable, Show)
instance Player WiimotePlayer where
playerUpdate (WiimotePlayer wiimote) tank = do
state <- hwiidGetState wiimote
messages <- hwiidGetMesg wiimote
let buttons = stateButtons state
shoot = any (\m -> (mesgType m == hwiidMesgTypeButton) && (test (mesgButtons m) hwiidButtonB)) $ messages
foo = any (\m -> (mesgType m == hwiidMesgTypeButton) && (test (mesgButtons m) hwiidButtonA)) $ messages
x = (if (test buttons hwiidButtonLeft) then (-1) else 0) + (if (test buttons hwiidButtonRight) then 1 else 0)
y = (if (test buttons hwiidButtonDown) then (-1) else 0) + (if (test buttons hwiidButtonUp) then 1 else 0)
ext = stateExt state
(mx, my) <- if (extType ext) /= hwiidExtNunchuk
then return (x, y)
else do
let nx = ((fromIntegral . extNunchukStickX $ ext) - 0x80)/0x80
ny = ((fromIntegral . extNunchukStickY $ ext) - 0x80)/0x80
return $ if (nx*nx + ny*ny) < 0.4 then (x, y) else (x+nx, y+ny)
--ax = aimx - (fromRational . toRational . tankX $ tank)
--ay = aimy - (fromRational . toRational . tankY $ tank)
let move = (mx /= 0 || my /= 0)
angle = if move then Just $ fromRational $ round ((atan2 my mx)*1000000*180/pi)%1000000 else Nothing
--aangle = if (ax /= 0 || ay /= 0) then Just $ fromRational $ round ((atan2 ay ax)*1000000*180/pi)%1000000 else Nothing
when foo $ print state
return (WiimotePlayer wiimote, angle, move, Nothing, shoot)
newWiimotePlayer :: IO WiimotePlayer
newWiimotePlayer = do
wiimote <- hwiidOpen bdAddrAny (hwiidFlagMesgInterface .|. hwiidFlagNonblock)
when (wiimote == nullWiimote) $ fail "Wiimote error"
hwiidSetReportMode wiimote (hwiidReportButtons .|. hwiidReportIR .|. hwiidReportNunchuk)
return $ WiimotePlayer wiimote
test :: (Bits a) => a -> a -> Bool
test field bits = (field .&. bits) == bits