{-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances #-} module BasicTypes where import FRP.Yampa import FRP.Yampa.Geometry import qualified Graphics.UI.SDL as SDL (Pixel, Event) import Physics ------------------------------------------------------------------------------ type ObjId = Int data OnFoot = LeftFoot | RightFoot | NoFoot deriving (Eq, Show) data PlayerRole = Goalie | Defender | Midfielder | Forward deriving (Eq, Show, Read) data Team = Home | Away deriving (Eq, Show) type TeamInfo = (Team, -- True = Home, False = Away SDL.Pixel, -- Team color 1 SDL.Pixel) -- Team color 2 data PlayerInfo = PlayerInfo { piNumber :: Int -- Number on jersey ,piPlayerRole :: PlayerRole -- "Left Defensive", "Center Forward", ... ,piBasePosDefense :: Point2 Double -- Base Defensive Position ,piBasePosOffense :: Point2 Double -- Base Offensive Position ,piPlayerSpeedMax :: Double ,piPlayerAccMax :: Double ,piPlayerCoverRatio :: Double -- defines how close a player covers his oppenent (~0: very close; ~1 very loose) } deriving (Show) data TimerEvent = TimerCalculateHomeAI | TimerCalculateAwayAI | TimerCalculateFacts | NoTimerEvent deriving (Show, Eq) type CurrentTime = Time type StateTime = Time type GameInput = (CurrentTime, [SDL.Event]) type Input = (Event TimerEvent, GameInput) type FactFunction = [FactParam] -> Maybe FactParam instance Show FactFunction where show _ = "FactFunction" data Facts = Facts { factCanIntercept :: FactFunction , factIsCloseTo :: FactFunction , factInLineWith :: FactFunction , factBestFreePlayer :: FactFunction -- Player, Value of Spot, Spot , factNearestAIPlayer :: FactFunction , factBallIsFree :: FactFunction -- current pos and projection in one secone , factAttacking :: FactFunction , factThrowingIn :: FactFunction , factBestPosition :: FactFunction -- current and best spot , factKickOff :: FactFunction , factBallCarrier :: FactFunction -- Player, Value of Spot, Spot , factPlayerSpot :: FactFunction -- Player, Value of Spot, Spot , factSpotValue :: FactFunction -- Player, Value of Spot, Spot , factBestShootingVector :: FactFunction , factBestPassingVector :: FactFunction , factPunt :: FactFunction , factIdling :: FactFunction , factWhoAmI :: FactFunction , factEq :: FactFunction , factGT :: FactFunction , factGetVector :: FactFunction } -- deriving (Show) --ACHTUNG: Funktion NFA, rnf definieren!!! data FactParam = FPTeam Team | FPEmpty | FPPlayers [ObjId] | FPSpot Spot | FPFromTo Spot Spot | FPScalar Double | FPVector Velocity3 | FPPlayer ObjId Double Spot | FPPlayerId ObjId | FPPlayerVector ObjId Velocity3 deriving (Show, Eq) data OutOfPlay = OOPSideOut | OOPKickOff | OOPBaseOut | OOPOffsite | InPlay deriving (Show, Eq) data Spot = Spot !Double !Double deriving (Show, Eq) data GridElement = GridElement !Spot !Double !Double deriving (Show, Eq) type Grid = [GridElement]