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.
 
 
 
 
 

32 lines
1.1 KiB

{-# 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{..}