module Grid where import Data.List import Data.Ord import Control.Monad import Global import BasicTypes import Helper import Object grid :: Param -> Double -> Double -> Grid grid param m n = let plm = pPitchWidth param / m plm2 = plm / 2 pln = pPitchLength param / n pln2 = pln / 2 in [GridElement(Spot x y) (homeValue param (Spot x y)) (awayValue param (Spot x y)) | i <- [1..m], j <- [1..n], let x = i * plm - plm2, let y = j * pln - pln2] viableSpot :: [VisibleState] -> Team -> Spot -> Spot -> Bool viableSpot vss team _ destSpot = -- "viable" means: at least one of "my" players is nearer to the spot -- than every player of the "other" team -- AND the spot is close enough so that one can pass or -- throw to it... let myTeam = map (projectP . vsPos) $ teamPlayers team vss others = map (projectP . vsPos) $ teamPlayers (otherTeam team) vss myNearest = minimumBy (distanceToSpot destSpot) myTeam theirNearest = minimumBy (distanceToSpot destSpot) others in spotDistance destSpot myNearest < spotDistance destSpot theirNearest -- AND-part yet missing -- simple function for ball shooting parameter --calculateVector :: Spot -> Spot -> Velocity3 --calculateVector (Spot sourceX sourceY) (Spot destX destY) = -- let diff = (Point2 sourceX sourceY) .-. (Point2 destX destY) -- dir = atan2 (vector2Y diff) (vector2X diff) -- base = fromPolar dir 10 -- addon = 0.1 *^ diff -- result = base ^+^ addon -- in vector3 (vector2X result) (vector2Y result) 2 spotValue :: [VisibleState] -> Team -> GridElement -> Double spotValue _ team (GridElement _ homeValue_ awayValue_) = -- the value of a spot is defined by the corresponding value in the -- grid plus a value stating how "free" the spot is from enemy players let gridValue = if team == Home then homeValue_ else awayValue_ freeValue = 0 -- missing yet in gridValue + freeValue spotFromGE :: GridElement -> Spot spotFromGE (GridElement spot _ _) = spot homeValueFromGE :: GridElement -> Double homeValueFromGE (GridElement _ homeValue_ _) = homeValue_ awayValueFromGE :: GridElement -> Double awayValueFromGE (GridElement _ _ awayValue_) = awayValue_ -- was wenn kein spot da? dann sollte das nicht hinkacheln, vielleicht besser -- maybe spot zurückgeben bestSpot :: [VisibleState] -> Team -> Spot -> Grid -> Spot bestSpot vss team currSpot = spotFromGE . maximumBy (compareSpots vss team) . filter (viableSpot vss team currSpot . spotFromGE) -- die bearbeitungsreihenfolge ist vielleicht etwas doof, weil die viableSpot -- berechnung mit der ganzen sortiererei vielleicht etwas aufwändiger ist als -- die bewertung der spots compareSpots :: [VisibleState] -> Team -> GridElement -> GridElement -> Ordering compareSpots vss = comparing . spotValue vss putGrid :: Param -> t -> t1 -> IO () putGrid param _ _ = forM_ (grid param 10 10) $ \(GridElement (Spot x y) vx vy) -> putStrLn $ show x ++ "; " ++ show y ++ "; " ++ show vx ++ "; " ++ show vy