parent
40eeaa0504
commit
910fa093bc
13 changed files with 248 additions and 456 deletions
@ -0,0 +1,32 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module Worldcup.Continents (Continents, Continent(..), parseContinents, lookupContinent) where |
||||
|
||||
import Data.Aeson |
||||
import Data.Aeson.Types as AET |
||||
import Data.HashMap.Strict as HM |
||||
import Data.Maybe as M |
||||
import Prelude as P |
||||
|
||||
type Continents = HashMap Int Continent |
||||
|
||||
data Continent = Continent { |
||||
continentId :: Int, |
||||
continentName :: String } deriving (Show) |
||||
|
||||
parseContinents :: Either String [Value] -> Continents |
||||
parseContinents (Left x) = error x |
||||
parseContinents (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Continent) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (continentId v) v acc |
||||
|
||||
lookupContinent :: Int -> Continents -> Continent |
||||
lookupContinent _id hm = M.fromMaybe (Continent 999 "DNE") (HM.lookup _id hm) |
||||
|
||||
instance FromJSON Continent where |
||||
parseJSON = withObject "continent" $ \o -> do |
||||
continentId <- o .: "id" |
||||
continentName <- o .: "name" |
||||
return Continent{..} |
@ -0,0 +1,34 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module Worldcup.Countries (Countries, Country(..), parseCountries, lookupCountry) where |
||||
|
||||
import Data.Aeson |
||||
import Data.Aeson.Types as AET |
||||
import Data.HashMap.Strict as HM |
||||
import Data.Maybe as M |
||||
import Prelude as P |
||||
|
||||
type Countries = HashMap Int Country |
||||
|
||||
data Country = Country { |
||||
countryId :: Int, |
||||
countryContinentId :: Int, |
||||
countryName :: String } deriving (Show) |
||||
|
||||
instance FromJSON Country where |
||||
parseJSON = withObject "country" $ \o -> do |
||||
countryId <- o .: "id" |
||||
countryContinentId <- o .: "continent_id" |
||||
countryName <- o .: "name" |
||||
return Country{..} |
||||
|
||||
lookupCountry :: Int -> Countries -> Country |
||||
lookupCountry _id hm = M.fromMaybe (Country 999 999 "DNE") (HM.lookup _id hm) |
||||
|
||||
parseCountries :: Either String [Value] -> Countries |
||||
parseCountries (Left x) = error x |
||||
parseCountries (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Country) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (countryId v) v acc |
@ -0,0 +1,32 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module Worldcup.Events (Events, Event(..), parseEvents, lookupEvent) where |
||||
|
||||
import Data.Aeson |
||||
import Data.Aeson.Types as AET |
||||
import Data.HashMap.Strict as HM |
||||
import Data.Maybe as M |
||||
import Prelude as P |
||||
|
||||
type Events = HashMap Int Event |
||||
|
||||
data Event = Event { |
||||
eventId :: Int, |
||||
eventName :: String } deriving (Show) |
||||
|
||||
instance FromJSON Event where |
||||
parseJSON = withObject "event" $ \o -> do |
||||
eventId <- o .: "id" |
||||
eventName <- o .: "key" |
||||
return Event{..} |
||||
|
||||
lookupEvent :: Int -> Events -> Event |
||||
lookupEvent _id es = M.fromMaybe (Event 999 "DNE") (HM.lookup _id es) |
||||
|
||||
parseEvents :: Either String [Value] -> Events |
||||
parseEvents (Left x) = error x |
||||
parseEvents (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Event) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (eventId v) v acc |
@ -0,0 +1,23 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module Worldcup.EventsTeams (EventTeam(..), parseEventsTeams) where |
||||
|
||||
import Data.Aeson |
||||
import Data.Aeson.Types |
||||
import Prelude as P |
||||
|
||||
data EventTeam = EventTeam { |
||||
eventTeamId :: Int } deriving (Show) |
||||
|
||||
instance FromJSON EventTeam where |
||||
parseJSON = withObject "team" $ \o -> do |
||||
eventTeamId <- o .: "team_id" |
||||
return EventTeam{..} |
||||
|
||||
parseEventsTeams :: Either String [Value] -> [Int] |
||||
parseEventsTeams (Left x) = error x |
||||
parseEventsTeams (Right xs) = P.foldl reduce [] xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String EventTeam) of |
||||
(Left s) -> error s |
||||
(Right v) -> eventTeamId v : acc |
@ -0,0 +1,40 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module Worldcup.Games (Game(..), parseGames) where |
||||
|
||||
import Data.Aeson |
||||
import Data.Aeson.Types |
||||
|
||||
data Game = Game { |
||||
roundId :: Int, |
||||
playAt :: String, |
||||
team1Id :: Int, |
||||
team2Id :: Int, |
||||
score1 :: Value, |
||||
score2 :: Value, |
||||
score1et :: Value, |
||||
score2et :: Value, |
||||
score1p :: Value, |
||||
score2p :: Value } deriving (Show) |
||||
|
||||
instance FromJSON Game where |
||||
parseJSON = withObject "game" $ \o -> do |
||||
roundId <- o .: "round_id" |
||||
team1Id <- o .: "team1_id" |
||||
team2Id <- o .: "team2_id" |
||||
playAt <- o .: "play_at" |
||||
score1 <- o .: "score1" |
||||
score2 <- o .: "score2" |
||||
score1et <- o .: "score1et" |
||||
score2et <- o .: "score2et" |
||||
score1p <- o .: "score1p" |
||||
score2p <- o .: "score2p" |
||||
return Game{..} |
||||
|
||||
parseGames :: Either String [Value] -> [Game] |
||||
parseGames (Left x) = error x |
||||
parseGames (Right xs) = foldl reduce [] xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Game) of |
||||
(Left s) -> error s |
||||
(Right v) -> v : acc |
@ -0,0 +1,34 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module Worldcup.Rounds (Rounds, Round(..), parseRounds, lookupRound) where |
||||
|
||||
import Data.Aeson |
||||
import Data.Aeson.Types as AET |
||||
import Data.HashMap.Strict as HM |
||||
import Data.Maybe as M |
||||
import Prelude as P |
||||
|
||||
type Rounds = HashMap Int Round |
||||
|
||||
data Round = Round { |
||||
roundId :: Int, |
||||
roundEventId :: Int, |
||||
roundName :: String } deriving (Show) |
||||
|
||||
parseRounds :: Either String [Value] -> Rounds |
||||
parseRounds (Left x) = error x |
||||
parseRounds (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Round) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (roundId v) v acc |
||||
|
||||
lookupRound :: Int -> Rounds -> Round |
||||
lookupRound _id hm = M.fromMaybe (Round 999 999 "DNE") (HM.lookup _id hm) |
||||
|
||||
instance FromJSON Round where |
||||
parseJSON = withObject "round" $ \o -> do |
||||
roundId <- o .: "id" |
||||
roundEventId <- o .: "event_id" |
||||
roundName <- o .: "title" |
||||
return Round{..} |
@ -0,0 +1,32 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module Worldcup.Teams (Teams, Team(..), parseTeams, lookupTeam) where |
||||
|
||||
import Data.Aeson |
||||
import Data.Aeson.Types |
||||
import Data.HashMap.Strict as HM |
||||
import Data.Maybe as M |
||||
import Prelude as P |
||||
|
||||
type Teams = HashMap Int Team |
||||
|
||||
data Team = Team { |
||||
teamId :: Int, |
||||
teamCountryId :: Int } deriving (Show) |
||||
|
||||
instance FromJSON Team where |
||||
parseJSON = withObject "team" $ \o -> do |
||||
teamId <- o .: "id" |
||||
teamCountryId <- o .: "country_id" |
||||
return Team{..} |
||||
|
||||
parseTeams :: Either String [Value] -> Teams |
||||
parseTeams (Left x) = error x |
||||
parseTeams (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Team) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (teamId v) v acc |
||||
|
||||
lookupTeam :: Int -> Teams -> Team |
||||
lookupTeam _id hm = M.fromMaybe (Team 999 999) (HM.lookup _id hm) |
@ -1,98 +0,0 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
import Data.Aeson as AE |
||||
import Data.Aeson.Types as AET |
||||
import Data.ByteString.Lazy as BL |
||||
import Data.ByteString.Lazy.Char8 as BL8 |
||||
import Prelude as P |
||||
|
||||
-- THIS "id":1 |
||||
-- "key":null CHECKED, NULL |
||||
-- THIS "round_id":1 round title join |
||||
-- "pos":1 RANKING? NOT USING |
||||
-- "group_id":null |
||||
-- THIS "team1_id":45 |
||||
-- THIS "team2_id":30 |
||||
-- THIS "play_at":"2011-11-11 12:00:00.000000" |
||||
-- "postponed":"f" CHECKED, NULL |
||||
-- "play_at_v2":null CHECKED, NULL |
||||
-- "play_at_v3":null CHECKED, NULL |
||||
-- "ground_id":null CHECKED, NULL |
||||
-- "city_id":null CHECKED, NULL |
||||
-- "knockout":"f" |
||||
-- "home":"t" |
||||
-- THIS "score1":1 regular time |
||||
-- THIS "score2":0 regular time |
||||
-- THIS "score1et":null extended time |
||||
-- THIS "score2et":null extended time |
||||
-- THIS "score1p":null penalty time |
||||
-- THIS "score2p":null penalty time |
||||
-- |
||||
-- "score1i":null CHECKED, NULL |
||||
-- "score2i":null CHECKED, NULL |
||||
-- "score1ii":null CHECKED, NULL |
||||
-- "score2ii":null CHECKED, NULL |
||||
-- "next_game_id":null CHECKED, NULL |
||||
-- "prev_game_id":null CHECKED, NULL |
||||
-- "winner":1 |
||||
-- "winner90":1 |
||||
-- "created_at":"2016-09-28 03:35:02.277055" |
||||
-- "updated_at":"2016-09-28 03:35:02.277055" |
||||
|
||||
data Game = Game { |
||||
round_id :: Value, |
||||
team1_id :: Value, |
||||
team2_id :: Value, |
||||
playAt :: Value, |
||||
score1 :: Value, |
||||
score2 :: Value, |
||||
score1et :: Value, |
||||
score2et :: Value, |
||||
score1p :: Value, |
||||
score2p :: Value } deriving (Show) |
||||
|
||||
instance ToJSON Game where |
||||
toJSON Game{..} = object [ |
||||
"rId" .= round_id, |
||||
"t1" .= team1_id, |
||||
"t2" .= team2_id, |
||||
"ts" .= playAt, |
||||
"s1" .= score1, |
||||
"s2" .= score2, |
||||
"s1e" .= score1et, |
||||
"s2e" .= score2et, |
||||
"s1p" .= score1p, |
||||
"s2p" .= score2p ] |
||||
|
||||
instance FromJSON Game where |
||||
parseJSON = withObject "game" $ \o -> do |
||||
round_id <- o .: "round_id" |
||||
team1_id <- o .: "team1_id" |
||||
team2_id <- o .: "team2_id" |
||||
playAt <- o .: "play_at" |
||||
score1 <- o .: "score1" |
||||
score2 <- o .: "score2" |
||||
score1et <- o .: "score1et" |
||||
score2et <- o .: "score2et" |
||||
score1p <- o .: "score1p" |
||||
score2p <- o .: "score2p" |
||||
return Game{..} |
||||
|
||||
reduce :: [Game] -> Value -> [Game] |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Game) of |
||||
(Left s) -> error s |
||||
(Right v) -> v : acc |
||||
|
||||
parseGames :: Either String [Value] -> [Game] |
||||
parseGames (Left x) = error x |
||||
parseGames (Right xs) = P.foldl reduce [] xs |
||||
|
||||
main :: IO () |
||||
main = do |
||||
src <- BL.readFile "./data/games.json" |
||||
let games = parseGames (AE.eitherDecode src :: Either String [Value]) |
||||
let encoded = encode games |
||||
BL8.putStrLn encoded |
||||
BL8.putStrLn "Writing games.json" |
||||
BL.writeFile "games.json" encoded |
@ -1,43 +0,0 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
import Data.Aeson as AE |
||||
import Data.Aeson.Types as AET |
||||
import Data.ByteString.Lazy as BL |
||||
import Data.ByteString.Lazy.Char8 as BL8 |
||||
import Data.HashMap.Strict as HM |
||||
import Prelude as P |
||||
|
||||
data Round = Round { _id :: Value, title :: Value } deriving (Show) |
||||
|
||||
instance ToJSON Round where |
||||
toJSON Round{..} = object [ "i" .= _id, "t" .= title ] |
||||
|
||||
instance FromJSON Round where |
||||
parseJSON = withObject "round" $ \o -> do |
||||
_id <- o .: "id" |
||||
title <- o .: "title" |
||||
return Round{..} |
||||
|
||||
reduce :: [Round] -> Value -> [Round] |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Round) of |
||||
(Left s) -> error s |
||||
(Right v) -> v : acc |
||||
|
||||
parseRounds :: Either String [Value] -> [Round] |
||||
parseRounds (Left x) = error x |
||||
parseRounds (Right xs) = P.foldl reduce [] xs |
||||
|
||||
parseResult :: [Round] -> [(String, Value)] |
||||
parseResult = P.foldl (\acc x -> (extractId x, title x) : acc) [] |
||||
where |
||||
extractId = BL8.unpack . encode . _id |
||||
|
||||
main :: IO () |
||||
main = do |
||||
src <- BL.readFile "./data/rounds.json" |
||||
let teams = parseRounds (AE.eitherDecode src :: Either String [Value]) |
||||
let encoded = encode $ HM.fromList $ parseResult teams |
||||
BL8.putStrLn encoded |
||||
BL8.putStrLn "Writing rounds.json" |
||||
BL.writeFile "rounds.json" encoded |
@ -1,187 +0,0 @@ |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
import Data.Aeson as AE |
||||
import Data.Aeson.Types as AET |
||||
import Data.ByteString.Lazy as BL |
||||
import Data.ByteString.Lazy.Char8 as BL8 |
||||
import Data.HashMap.Strict as HM |
||||
import Data.Maybe as M |
||||
import Prelude as P |
||||
|
||||
----- Data constructors ----- |
||||
data TeamFinal = TeamFinal { |
||||
resultId :: Int, |
||||
resultCountry :: String, |
||||
resultContinent :: String, |
||||
resultGoals :: Int |
||||
} deriving (Show) |
||||
|
||||
data Team = Team { |
||||
teamId :: Int, |
||||
teamCountryId :: Int } deriving (Show) |
||||
|
||||
data EventTeam = EventTeam { |
||||
eventTeamId :: Int } deriving (Show) |
||||
|
||||
data Country = Country { |
||||
countryId :: Int, |
||||
countryName :: String, |
||||
countryContinentId :: Int } deriving (Show) |
||||
|
||||
data Continent = Continent { |
||||
continentId :: Int, |
||||
continentName :: String } deriving (Show) |
||||
|
||||
data Game = Game { |
||||
roundId :: Int, |
||||
playAt :: String, |
||||
team1Id :: Int, |
||||
team2Id :: Int, |
||||
score1 :: Value, |
||||
score2 :: Value, |
||||
score1et :: Value, |
||||
score2et :: Value, |
||||
score1p :: Value, |
||||
score2p :: Value } deriving (Show) |
||||
|
||||
----- Type synonyms ----- |
||||
type Teams = HashMap Int Team |
||||
type Countries = HashMap Int Country |
||||
type Continents = HashMap Int Continent |
||||
|
||||
----- ToJSON parsers ----- |
||||
instance ToJSON TeamFinal where |
||||
toJSON TeamFinal{..} = |
||||
object [ "id" .= resultId, "ct" .= resultCountry, "cn" .= resultContinent, "g" .= resultGoals ] |
||||
|
||||
----- FromJSON parsers ----- |
||||
instance FromJSON Team where |
||||
parseJSON = withObject "team" $ \o -> do |
||||
teamId <- o .: "id" |
||||
teamCountryId <- o .: "country_id" |
||||
return Team{..} |
||||
|
||||
instance FromJSON EventTeam where |
||||
parseJSON = withObject "team" $ \o -> do |
||||
eventTeamId <- o .: "team_id" |
||||
return EventTeam{..} |
||||
|
||||
instance FromJSON Game where |
||||
parseJSON = withObject "game" $ \o -> do |
||||
roundId <- o .: "round_id" |
||||
team1Id <- o .: "team1_id" |
||||
team2Id <- o .: "team2_id" |
||||
playAt <- o .: "play_at" |
||||
score1 <- o .: "score1" |
||||
score2 <- o .: "score2" |
||||
score1et <- o .: "score1et" |
||||
score2et <- o .: "score2et" |
||||
score1p <- o .: "score1p" |
||||
score2p <- o .: "score2p" |
||||
return Game{..} |
||||
|
||||
instance FromJSON Country where |
||||
parseJSON = withObject "country" $ \o -> do |
||||
countryId <- o .: "id" |
||||
countryName <- o .: "name" |
||||
countryContinentId <- o .: "continent_id" |
||||
return Country{..} |
||||
|
||||
instance FromJSON Continent where |
||||
parseJSON = withObject "continent" $ \o -> do |
||||
continentId <- o .: "id" |
||||
continentName <- o .: "name" |
||||
return Continent{..} |
||||
|
||||
parseTeams :: Either String [Value] -> Teams |
||||
parseTeams (Left x) = error x |
||||
parseTeams (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Team) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (teamId v) v acc |
||||
|
||||
parseEventTeams :: Either String [Value] -> [Int] |
||||
parseEventTeams (Left x) = error x |
||||
parseEventTeams (Right xs) = P.foldl reduce [] xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String EventTeam) of |
||||
(Left s) -> error s |
||||
(Right v) -> eventTeamId v : acc |
||||
|
||||
parseGames :: Either String [Value] -> [Game] |
||||
parseGames (Left x) = error x |
||||
parseGames (Right xs) = P.foldl reduce [] xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Game) of |
||||
(Left s) -> error s |
||||
(Right v) -> v : acc |
||||
|
||||
parseCountries :: Either String [Value] -> Countries |
||||
parseCountries (Left x) = error x |
||||
parseCountries (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Country) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (countryId v) v acc |
||||
|
||||
parseContinents :: Either String [Value] -> Continents |
||||
parseContinents (Left x) = error x |
||||
parseContinents (Right xs) = P.foldl reduce HM.empty xs where |
||||
reduce acc x = case (parseEither parseJSON x :: Either String Continent) of |
||||
(Left s) -> error s |
||||
(Right v) -> HM.insert (continentId v) v acc |
||||
|
||||
parseInt :: Value -> Int |
||||
parseInt Null = 0 |
||||
parseInt x = read $ BL8.unpack $ encode x :: Int |
||||
|
||||
----- Hashmap lookup convenience ----- |
||||
lookupTeam :: Int -> Teams -> Team |
||||
lookupTeam _id hm = M.fromMaybe (Team 999 999) (HM.lookup _id hm) |
||||
|
||||
lookupCountry :: Int -> Countries -> Country |
||||
lookupCountry _id hm = M.fromMaybe (Country 999 "Unknown" 999) (HM.lookup _id hm) |
||||
|
||||
lookupContinent :: Int -> Continents -> Continent |
||||
lookupContinent _id hm = M.fromMaybe (Continent 999 "Unknown") (HM.lookup _id hm) |
||||
|
||||
countryFromTeamId :: Int -> Teams -> Countries -> Country |
||||
countryFromTeamId _id hmT = lookupCountry a where |
||||
a = teamCountryId $ lookupTeam _id hmT |
||||
|
||||
continentFromTeamId :: Int -> Teams -> Countries -> Continents -> Continent |
||||
continentFromTeamId _id hmT hmC = lookupContinent (countryContinentId b) where |
||||
a = teamCountryId $ lookupTeam _id hmT |
||||
b = lookupCountry a hmC |
||||
|
||||
goalsFromTeamId :: Int -> [Game] -> Int |
||||
goalsFromTeamId _id = P.foldl reducer 0 where |
||||
reducer acc x |
||||
| team1Id x == _id = acc + parseInt (score1 x) + parseInt (score1et x) + parseInt (score1p x) |
||||
| team2Id x == _id = acc + parseInt (score2 x) + parseInt (score2et x) + parseInt (score2p x) |
||||
| otherwise = acc |
||||
|
||||
buildResult :: [Int] -> Teams -> Countries -> Continents -> [Game] -> [TeamFinal] |
||||
buildResult ets hmT hmC hmN gs = P.foldl reducer [] ets where |
||||
reducer acc x = TeamFinal x (getCountryName x) (getContinentName x) (goalCount x) : acc |
||||
getCountryName x = countryName (countryFromTeamId x hmT hmC) |
||||
getContinentName x = continentName (continentFromTeamId x hmT hmC hmN) |
||||
goalCount x = goalsFromTeamId x gs |
||||
|
||||
main :: IO () |
||||
main = do |
||||
dataTeams <- BL.readFile "./data/teams.json" |
||||
dataEventTeams <- BL.readFile "./data/events_teams.json" |
||||
dataCountries <- BL.readFile "./data/countries.json" |
||||
dataContinents <- BL.readFile "./data/continents.json" |
||||
dataGames <- BL.readFile "./data/games.json" |
||||
|
||||
let teams = parseTeams (AE.eitherDecode dataTeams) |
||||
let eventteams = parseEventTeams (AE.eitherDecode dataEventTeams) |
||||
let games = parseGames (AE.eitherDecode dataGames) |
||||
let countries = parseCountries (AE.eitherDecode dataCountries) |
||||
let continents = parseContinents (AE.eitherDecode dataContinents) |
||||
|
||||
let encoded = encode $ buildResult eventteams teams countries continents games |
||||
BL8.putStrLn encoded |
||||
P.putStrLn $ show (P.length eventteams) ++ " teams found." |
||||
BL8.putStrLn "Writing teams.json" |
||||
BL8.writeFile "teams.json" encoded |
@ -1 +0,0 @@ |
||||
[{"g":3,"ct":"Nigeria","cn":"Africa","id":20},{"g":4,"ct":"Côte d'Ivoire","cn":"Africa","id":17},{"g":1,"ct":"Cameroon","cn":"Africa","id":22},{"g":4,"ct":"Ghana","cn":"Africa","id":18},{"g":7,"ct":"Algeria","cn":"Africa","id":1},{"g":3,"ct":"Australia","cn":"Pacific","id":193},{"g":1,"ct":"Iran","cn":"Middle East","id":178},{"g":2,"ct":"Japan","cn":"Asia","id":72},{"g":3,"ct":"South Korea","cn":"Asia","id":74},{"g":13,"ct":"Costa Rica","cn":"Central America","id":118},{"g":5,"ct":"United States","cn":"North America","id":191},{"g":1,"ct":"Honduras","cn":"Central America","id":117},{"g":5,"ct":"México","cn":"North America","id":190},{"g":14,"ct":"Brazil","cn":"South America","id":211},{"g":12,"ct":"Argentina","cn":"South America","id":210},{"g":12,"ct":"Colombia","cn":"South America","id":215},{"g":8,"ct":"Chile","cn":"South America","id":212},{"g":3,"ct":"Ecuador","cn":"South America","id":216},{"g":4,"ct":"Uruguay","cn":"South America","id":214},{"g":6,"ct":"Belgium","cn":"Europe","id":125},{"g":18,"ct":"Germany","cn":"Europe","id":127},{"g":2,"ct":"Italy","cn":"Europe","id":134},{"g":21,"ct":"Netherlands","cn":"Europe","id":137},{"g":7,"ct":"Switzerland","cn":"Europe","id":153},{"g":4,"ct":"Bosnia and Herzegovina","cn":"Europe","id":162},{"g":2,"ct":"Russia","cn":"Europe","id":156},{"g":4,"ct":"Spain","cn":"Europe","id":129},{"g":2,"ct":"England","cn":"Europe","id":170},{"g":6,"ct":"Greece","cn":"Europe","id":132},{"g":6,"ct":"Croatia","cn":"Europe","id":154},{"g":4,"ct":"Portugal","cn":"Europe","id":138},{"g":10,"ct":"France","cn":"Europe","id":131}] |
Loading…
Reference in new issue