You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 
 

47 lines
1.7 KiB

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Worldcup.Tourneys (Tourneys, Tourney(..), buildTourneys) where
import Data.Aeson
import Data.HashMap.Strict as HM
import Prelude as P
import Worldcup.Countries
import Worldcup.Events
import Worldcup.EventsTeams
import Worldcup.Games
import Worldcup.Rounds
import Worldcup.Squads
import Worldcup.Teams
type Tourneys = HashMap String Tourney
data Tourney = Tourney {
tourneyGames :: [Game],
tourneySquads :: [Squad] } deriving (Show)
instance ToJSON Tourney where
toJSON Tourney{..} = object [ "games" .= tourneyGames, "teams" .= tourneySquads ]
roundIsInEvent :: Int -> Int -> Rounds -> Bool
roundIsInEvent eid rid rs = roundEventId getRound == eid where
getRound = lookupRound rid rs
teamIdsFromEventId :: Int -> [EventTeam] -> [Int]
teamIdsFromEventId eid = foldl reducer [] where
reducer acc x
| eventsTeamsEventId x == eid = eventsTeamsTeamId x : acc
| otherwise = acc
gamesFromEventId :: Int -> Rounds -> [Game] -> [Game]
gamesFromEventId eid rs = foldl reducer [] where
reducer acc x
| roundIsInEvent eid (gameRoundId x) rs = x : acc
| otherwise = acc
buildTourneys :: Countries -> Rounds -> [EventTeam] -> Teams -> [Game] -> [Event] -> Tourneys
buildTourneys cs rs ets ts gs = foldl reducer HM.empty where
reducer acc x = HM.insert (getEvent x) (Tourney (getGames x) (getSquads x)) acc
getGames x = gamesFromEventId (eventId x) rs gs
getSquads x = buildSquads cs gs ts (teamIdsFromEventId (eventId x) ets)
getEvent x = drop 6 (eventName x)