{-# LANGUAGE UnicodeSyntax, Rank2Types, ExistentialQuantification #-}
module SoccerFun.Types where

import Control.Monad.State
import SoccerFun.Geometry

data Half = FirstHalf | SecondHalf deriving (Eq,Show)
type PlayingTime = Minutes

-- | type with an inverse value
class Other a where other  a  a

type TimeUnit = Seconds -- ^ time unit in sec.
type Seconds = Float -- ^ zero < time unit

data Edge = North | South deriving (Eq,Show)

data PlayerID = PlayerID {clubName  ClubName, playerNo  PlayersNumber} deriving (Show,Eq)
type ClubName = String
type PlayersNumber = Int

--thinkS ∷ inp → State (Brain inp out) out
--thinkS i = do
--	Brain m ai ← get
--	let (o, m') = runState (ai i) m
--	put $ Brain m' ai
--	return o

--think ∷ Brain inp out → inp → (Brain inp out, out)
--think (Brain m ai) i = (Brain m' ai, o) where
--	(o, m') = runState (ai i) m


-- | If the referee gives a second yellow he should add red to it himself
data Reprimand = Warning | YellowCard | RedCard deriving (Show, Eq)

data Success = Success | Fail deriving (Show, Eq)

type FramesToGo = Int -- ^ number of frames to go before event ends

data RefereeAction
	= ReprimandPlayer PlayerID Reprimand -- ^ player with given name receives reprimand
	| Hands PlayerID -- ^ person is seen for doing hands
	| TackleDetected PlayerID -- ^ person is seen for doing tackle
	| SchwalbeDetected PlayerID -- ^ person is seen for doing schwalbe
	| TheaterDetected PlayerID
	| DangerousPlay PlayerID -- ^ person is seen for doing dangerous actions
	| GameOver -- ^ end of game
	| PauseGame -- ^ game is paused
	| AddTime ExtraTime -- ^ extra time is added to the game
	| EndHalf -- ^ first half is over, teams go for a second half
	| Goal ATeam -- ^ team playing at home has scored
	| Offside PlayerID -- ^ player is offside at Home
	| DirectFreeKick ATeam Position -- ^ a direct free kick is granted for team home at given position
	| GoalKick ATeam -- ^ a goal kick is granted for team home
	| Corner ATeam Edge -- ^ a corner kick is granted for team home
	| ThrowIn ATeam Position -- ^ a throw in ball is granted for team home at given position
	| Penalty ATeam -- ^ penalty at homeside
	| CenterKick ATeam -- ^ team playing at home may start from the center
	| Advantage ATeam -- ^ referee gives advantages to home-team
	| OwnBallIllegally PlayerID -- ^ ball was for the other team
	| DisplacePlayers Displacements -- ^ displaces all players at the provided position (used with free kicks)
	| ContinueGame
	| TellMessage String -- ^ no effect on match, message is displayed by referee
	deriving (Show, Eq)

data ATeam = Team1 | Team2 deriving (Eq, Show)

type Displacements = [(PlayerID,Displacement)] -- ^ players that need to be displaced
type Displacement = Position -- ^ new position

type ExtraTime = Minutes
type Minutes = Float