Finished JSON extraction.

master
Ben Burlingham 9 years ago
parent 41ddeb6fc9
commit 1fe1790ae7
  1. 4
      Worldcup/Continents.hs
  2. 3
      Worldcup/Countries.hs
  3. 63
      Worldcup/Squads.hs
  4. 6
      Worldcup/Teams.hs
  5. 1
      Worldcup/Tourneys.hs
  6. 59
      worldcup.hs
  7. 1
      worldcup.json

@ -7,6 +7,7 @@ import Data.Aeson
import Data.Aeson.Types as AET
import Data.HashMap.Strict as HM
import Data.Maybe as M
import Data.Text as T
import Prelude as P
type Continents = HashMap Int Continent
@ -15,6 +16,9 @@ data Continent = Continent {
continentId :: Int,
continentName :: String } deriving (Show)
instance ToJSON Continent where
toJSON Continent{..} = String $ T.pack continentName
parseContinents :: Either String [Value] -> Continents
parseContinents (Left x) = error x
parseContinents (Right xs) = P.foldl reduce HM.empty xs where

@ -16,6 +16,9 @@ data Country = Country {
countryContinentId :: Int,
countryName :: String } deriving (Show)
instance ToJSON Country where
toJSON Country{..} = object [ "cId" .= countryContinentId, "n" .= countryName ]
instance FromJSON Country where
parseJSON = withObject "country" $ \o -> do
countryId <- o .: "id"

@ -0,0 +1,63 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Worldcup.Squads (Squad(..), buildSquads) where
import Data.Aeson
import Data.Aeson.Types
import Data.HashMap.Strict as HM
import Data.Maybe as M
import Prelude as P
import Worldcup.Continents
import Worldcup.Countries
import Worldcup.Events
import Worldcup.EventsTeams
import Worldcup.Games
import Worldcup.Rounds
import Worldcup.Teams
import Worldcup.Tourneys
data Squad = Squad {
squadCountryId :: String,
squadContinentId :: String,
squadGoalsFor :: Int,
squadGoalsAgainst :: Int
} deriving (Show)
instance ToJSON Squad where
toJSON Squad{..} =
object [ "id" .= squadId,
"ct" .= squadCountry,
"cn" .= squadContinent,
"g" .= squadGoals ]
buildSquads :: [Squad]
buildSquads = []
-- countryFromTeamId :: Int -> Teams -> Countries -> Country
-- countryFromTeamId _id ts = lookupCountry a where
-- a = teamCountryId $ lookupTeam _id ts
--
-- parseInt :: Value -> Int
-- parseInt Null = 0
-- parseInt x = read $ BL8.unpack $ encode x :: Int
--
-- 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
--
-- buildFinalResult :: [Int] -> Teams -> Countries -> Continents -> [Game] -> [FinalResult]
-- buildFinalResult ets hmT hmC hmN gs = P.foldl reducer [] ets where
-- reducer acc x = FinalResult 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

@ -4,9 +4,10 @@
module Worldcup.Teams (Teams, Team(..), parseTeams, lookupTeam) where
import Data.Aeson
import Data.Aeson.Types
import Data.Aeson.Types as AET
import Data.HashMap.Strict as HM
import Data.Maybe as M
import Data.Scientific as S
import Prelude as P
type Teams = HashMap Int Team
@ -15,6 +16,9 @@ data Team = Team {
teamId :: Int,
teamCountryId :: Int } deriving (Show)
instance ToJSON Team where
toJSON Team{..} = Number $ scientific (P.toInteger teamCountryId) 0
instance FromJSON Team where
parseJSON = withObject "team" $ \o -> do
teamId <- o .: "id"

@ -4,7 +4,6 @@
module Worldcup.Tourneys (Tourneys, Tourney(..), buildTourneys) where
import Data.Aeson
import Data.Aeson.Types as AET
import Data.HashMap.Strict as HM
import Prelude as P
import Worldcup.Events

@ -2,11 +2,9 @@
{-# 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
import Worldcup.Continents
import Worldcup.Countries
@ -17,17 +15,6 @@ import Worldcup.Rounds
import Worldcup.Teams
import Worldcup.Tourneys
-- data FinalResult = FinalResult {
-- resultId :: Int,
-- resultCountry :: String,
-- resultContinent :: String,
-- resultGoals :: Int
-- } deriving (Show)
--
-- instance ToJSON FinalResult where
-- toJSON FinalResult{..} =
-- object [ "id" .= resultId, "ct" .= resultCountry, "cn" .= resultContinent, "g" .= resultGoals ]
data WorldcupData = WorldcupData {
worldcupTeams :: Teams,
worldcupCountries :: Countries,
@ -35,35 +22,12 @@ data WorldcupData = WorldcupData {
worldcupTourneys :: Tourneys
} deriving (Show)
parseInt :: Value -> Int
parseInt Null = 0
parseInt x = read $ BL8.unpack $ encode x :: Int
-- 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
--
-- buildFinalResult :: [Int] -> Teams -> Countries -> Continents -> [Game] -> [FinalResult]
-- buildFinalResult ets hmT hmC hmN gs = P.foldl reducer [] ets where
-- reducer acc x = FinalResult 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
buildWorldcupData :: WorldcupData
buildWorldcupData = WorldcupData HM.empty HM.empty HM.empty HM.empty
instance ToJSON WorldcupData where
toJSON WorldcupData{..} = object [
"teams" .= worldcupTeams,
"countries" .= worldcupCountries,
"continents" .= worldcupContinents,
"tourneys" .= worldcupTourneys ]
main :: IO ()
main = do
@ -83,9 +47,10 @@ main = do
let continents = parseContinents (AE.eitherDecode dataContinents)
let rounds = parseRounds (AE.eitherDecode dataRounds)
let encoded = encode $ buildTourneys rounds eventsteams games events
let tourneys = buildTourneys rounds eventsteams games events
let worldcup = WorldcupData teams countries continents tourneys
let encoded = encode worldcup
BL8.putStrLn encoded
-- P.putStrLn $ show (P.length eventteams) ++ " teams found."
-- BL8.putStrLn "Writing teams.json"
-- BL8.writeFile "teams.json" encoded
print "DONE"
BL8.putStrLn "Writing worldcup.json"
BL8.writeFile "worldcup.json" encoded

File diff suppressed because one or more lines are too long
Loading…
Cancel
Save