module RenderPlayer (renderPlayer, renderPlayerDebug) where import Data.Bits import GHC.Int import Data.Array import Control.Monad import Data.Time.Clock import FRP.Yampa.Geometry import Graphics.UI.SDL as SDL import Graphics.UI.SDL.Primitives as SDLp import Graphics.UI.SDL.TTF as SDLt import Graphics.UI.SDL.Mixer as SDLm import BasicTypes import RenderUtil import Global orange :: Pixel orange = rgbColor 0xE7 0x5B 0x12 -- Alles rund um den Fußballer... r1 :: Fractional a => a -> a r1 z = 3.0 + z -- Punkte zwischen Kreisrand und äußerem Ring r2 :: Fractional a => a -> a r2 z = 6.0 + z -- Punkte zwischen Kreisrand innerem Ring angle :: Double angle = 0.45 -- Winkel des Zeiger-Dreiecks pr1 :: (Integral b, RealFrac a) => a -> b pr1 z = truncate $ r1 z triangle :: (Floating a, Integral t2, Integral t1, RealFrac a) => t1 -> t2 -> t -> a -> a -> (t -> a) -> (t -> a) -> a -> ((t1, t2), (t1, t2), (t1, t2)) triangle x y height radD alpha r1' r2' angle' = let l1 = radD - (r1' height) l2 = radD - (r2' height) a = (x + truncate (l1 * cos alpha), y + truncate (l1 * sin alpha)) b = (x + truncate (l2 * cos (alpha-angle')), y + truncate (l2 * sin (alpha-angle'))) c = (x + truncate (l2 * cos (alpha+angle')), y + truncate (l2 * sin (alpha+angle'))) in (a,b,c) playersizeMin :: Int16 playersizeMin = 25 :: Int16 -- in Pixeln playersizeMax :: Int16 playersizeMax = 50 maxJump :: Double maxJump = 3.0 -- in Meter blinker :: IO Bool blinker = do t <- fmap utctDayTime getCurrentTime let tFrac = t - fromIntegral (truncate t) return $ tFrac < 0.5 playerSize :: Param -> Double -> Int16 playerSize param z = -- zwischen 0 und 2 Meter Höhe, dann wechselt der Spieler zwischen 30 und 50 Dicke... if z > maxJump then playersizeMax else if z < pGround param then playersizeMin else truncate $ fromIntegral playersizeMin + z * (fromIntegral playersizeMax - fromIntegral playersizeMin) / 10.0 renderPlayer :: (Num i, Num a, Ord a, Show a, Ix i) => Param -> Surface -> Point3 Double -> Double -> t -> a -> Pixel -> Pixel -> Pixel -> Bool -> Bool -> Bool -> Array i Font -> Chunk -> IO Bool renderPlayer param surface p alpha _ number cCircle cTriangle cBorder kicked nonai designated fonts wav = do when kicked $ playChannel (-1) wav 0 >> return () let Point3 px py pz = p let radius = playerSize param pz `shiftR` 1 let radius' = (radius `shiftR` 1)-4 -- hacky: try to align exactly with ball... let (x', y') = pitchToPoint param (px, py) let (x, y) = (x'+radius', y'+radius') let xAdjust = truncate (-0.4*pz) + if number > 9 then 5 else 2 :: Int16 -- Zentrieren der Rückennummer let yAdjust = if pz < 1 then 6 else if pz < 2 then 4 else 4 :: Int16 -- Zentrieren der Rückennummer let radD = fromIntegral radius let ((ax, ay), (bx, by), (cx, cy)) = triangle x y pz (2*radD) alpha r1 r2 angle let font = if pz < 1 then fonts ! 1 else if pz < 2 then fonts ! 2 else fonts ! 3 let markFont = fonts ! 5 blinkOn <- blinker let cBorderBlinking = if nonai && blinkOn then cCircle else cBorder let cTriangleBlinking = if nonai && blinkOn then cCircle else cTriangle let cCircleBlinking = if nonai && blinkOn then cBorder else cCircle fontSurface <- SDLt.renderTextSolid font (show number) (colorFromPixel cTriangleBlinking) -- f2 <- SDL.convertSurface fontSurface (SDL.surfaceGetPixelFormat surface) [] SDLp.filledCircle surface x y radius cBorderBlinking SDLp.filledCircle surface x y (radius - (pr1 pz)) cCircleBlinking when designated $ do markSurface <- SDLt.renderTextSolid markFont "!" (colorFromPixel orange) SDL.blitSurface markSurface Nothing surface (Just $ Rect (fromIntegral (x-xAdjust+1)) (fromIntegral (y-yAdjust-5)) (fromIntegral (x-xAdjust+10)) (fromIntegral (y-yAdjust+10))) return () SDLp.filledTrigon surface ax ay bx by cx cy cTriangleBlinking SDL.blitSurface fontSurface Nothing surface (Just $ Rect (fromIntegral (x-xAdjust)) (fromIntegral (y-yAdjust)) (fromIntegral (x-xAdjust+10)) (fromIntegral (y-yAdjust+10))) renderPlayerDebug :: (Show a1, Show a) => Surface -> t -> Int -> a1 -> a -> Pixel -> Font -> t1 -> t2 -> Team -> IO Bool renderPlayerDebug surface _ number bState tState color font _ _ oosTeam = do fontSurface <- SDLt.renderTextSolid font (show number ++ ": " ++ show tState ++ ", " ++ show bState ++ ", " -- ++ -- show baseDef ++ ", " ++ -- show baseOff ) (colorFromPixel color) -- f2 <- SDL.convertSurface fontSurface (SDL.surfaceGetPixelFormat surface) [] let adjust = if oosTeam == Home then 150 else 500 SDL.blitSurface fontSurface Nothing surface (Just $ Rect 850 (adjust+20*number) 950 (adjust+50+20*number))