module Topkata.Topka.Ghost where import Graphics.UI.GLUT import Topkata.Topka.Base import Vector import Labygen -- import Debug.Trace (trace) data GhostState = GhostState { ghostPosition :: Vector3 GLdouble, ghostOrientation :: Direction, ghostSpeed :: GLdouble, ghostPhase :: GLuint } newGhost x z = GhostState { ghostPosition = Vector3 x 0.5 z, ghostOrientation = East, ghostSpeed = 0.01, ghostPhase = 0 } drawGhost et pm phase = do texture Texture2D $= Enabled textureBinding Texture2D $= et --textureFunction $= Decal mapM_ (\ a -> drawSegment pm $ segment a (a+epsilon)) [0, epsilon .. pi+epsilon] color (Color3 0.0 1.0 (1.0 :: GLfloat)) mapM_ (\ y -> drawSegment pm $ ringSegment (-y) (-y-epsilon) phase) [0, epsilon .. pi+epsilon] texture Texture2D $= Disabled showGhosts ghosts tops = mapM_ (\ g -> showGhost g tops) ghosts ghostPhi = angleOfDirection . ghostOrientation showGhost ghost tops = preservingMatrix $ do let trans = ghostPosition ghost phase = ghostPhase ghost phi = ghostPhi ghost translate trans scale 0.3 0.3 (0.3 :: GLdouble) rotate (180*phi/pi-90) (Vector3 0 1 (0 :: GLfloat)) blend $= Enabled blendFunc $= (SrcAlpha, One) depthMask $= Disabled callList (DisplayList (tops+phase+52)) depthMask $= Enabled blend $= Disabled animateGhost rand laby ghost = let speed = ghostSpeed ghost dir = ghostOrientation ghost angle = angleOfDirection dir dx = speed * sin angle dz = speed * cos angle pos@(Vector3 x y z) = ghostPosition ghost (nx, nz) = (x+dx, z+dz) (wx, wz) = (nx+0.3*sin angle, nz +0.3 * cos angle) rot = if odd rand then rotCW else rotCCW rangle = angleOfDirection (rot dir) randomTurn = rand `mod` 25 == 0 && let (tx, tz) = (x+sin rangle, z + cos rangle) in not $ inWall laby (tx+1) (y+1) (tz+1) (newOrient, newPos) = if inWall laby wx y wz || randomTurn then (rot dir, pos) else (dir, Vector3 nx y nz) newSpeed = if newOrient == dir then min 0.039 (speed + 0.001) else 0.005 ghostPhase' = (ghostPhase ghost + 1) `mod` 51 ghost' = ghost { ghostOrientation = newOrient, ghostSpeed = newSpeed, ghostPosition = newPos, ghostPhase = ghostPhase'} in ghost'