{-# LANGUAGE UnicodeSyntax #-} module SoccerFun.Field where import SoccerFun.Geometry import SoccerFun.Types (Other (other)) data Field = Field {fwidth ∷ FieldWidth, -- ^ width of ball field (64m <=width <=75m) flength ∷ FieldLength -- ^ height of ball field (100m<=height<=110m) } deriving Show type FieldWidth = Metre type FieldLength = Metre defaultField ∷ Field defaultField = Field { fwidth = 75.0, flength = 110.0 } inPenaltyArea ∷ Field → Home → Position → Bool inPenaltyArea field home pos = northEdge <= py pos && py pos <= southEdge && if home == West then px pos <= westEdge else px pos >= eastEdge where northEdge = (fwidth field) / 2.0 - radiusPenaltyArea southEdge = (fwidth field) / 2.0 + radiusPenaltyArea westEdge = penaltyAreaDepth eastEdge = (flength field) - penaltyAreaDepth data Home = West | East deriving (Eq,Show) instance Other Home where other West = East other East = West isWest ∷ Home → Bool isWest West = True isWest _ = False isEast ∷ Home → Bool isEast East = True isEast _ = False -- | goalPoles yields the py coordinates of the north pole and south pole of the goal (note that north < south). goalPoles ∷ Field → (Metre,Metre) goalPoles field = (northPole,southPole) where northPole = ((fwidth field)-goalWidth)/2.0 southPole = northPole + goalWidth -- | Official metrics of a ball field: radiusCentreCircle = 9.15 ∷ Float goalWidth = 7.32 :: Float goalHeight = 2.44 :: Float goalAreaDepth = 5.50 :: Float radiusCornerKickArea = 0.90 :: Float -- | not official, taken for rendering goalPoleWidth = 0.4 :: Float -- | not official, taken for rendering radiusCentreSpot = 0.3 :: Float radiusPenaltySpot = 0.2 ∷ Metre radiusPenaltyArea = 9.15 ∷ Metre penaltyAreaDepth = 16.50 ∷ Metre penaltySpotDepth = 11.00 ∷ Metre