{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module NationStates.Nation (
Nation(..),
run,
name,
fullname,
type_,
motto,
category,
wa,
endorsements,
gavote,
scvote,
freedom,
region,
population,
tax,
animal,
animaltrait,
currency,
flag,
banner,
banners,
censusscore,
censusscore',
) where
import Control.Applicative
import Data.Maybe
import qualified Data.Map as Map
import qualified Data.MultiSet as MultiSet
import Text.XML.Light
import Prelude
import NationStates.Core
newtype Nation a = Nation { unNation :: NS a }
deriving (Functor, Applicative)
run
:: String
-> Nation a
-> Context
-> IO a
run nation = requestNS (Just ("nation", nation)) . unNation
name :: Nation String
name = Nation $ makeNS "name" "NAME"
fullname :: Nation String
fullname = Nation $ makeNS "fullname" "FULLNAME"
type_ :: Nation String
type_ = Nation $ makeNS "type" "TYPE"
motto :: Nation String
motto = Nation $ makeNS "motto" "MOTTO"
category :: Nation WACategory
category = Nation . fmap (expect "category" <*> readWACategory) $
makeNS "category" "CATEGORY"
wa :: Nation Bool
wa = Nation . fmap (expect "WA status" <*> readWAStatus) $ makeNS "wa" "UNSTATUS"
endorsements :: Nation [String]
endorsements = Nation . fmap (wordsBy (== ',')) $
makeNS "endorsements" "ENDORSEMENTS"
gavote :: Nation (Maybe WAVote)
gavote = Nation . fmap (expect "General Assembly vote" <*> readWAVote') $
makeNS "gavote" "GAVOTE"
scvote :: Nation (Maybe WAVote)
scvote = Nation . fmap (expect "Security Council vote" <*> readWAVote') $
makeNS "scvote" "SCVOTE"
freedom :: Nation (String, String, String)
freedom = Nation $ makeNS' (shard "freedom") parse
where
parse _ root
| Just parent <- findChild (unqual "FREEDOM") root
, [c, e, p] <- map strContent $ elChildren parent
= (c, e, p)
| otherwise
= error "could not find freedom descriptors"
region :: Nation String
region = Nation $ makeNS "region" "REGION"
population :: Nation Integer
population = Nation . fmap (expect "population" <*> readMaybe) $
makeNS "population" "POPULATION"
tax :: Nation Double
tax = Nation . fmap (expect "tax" <*> readMaybe) $
makeNS "tax" "TAX"
animal :: Nation String
animal = Nation $ makeNS "animal" "ANIMAL"
animaltrait :: Nation String
animaltrait = Nation $ makeNS "animaltrait" "ANIMALTRAIT"
currency :: Nation String
currency = Nation $ makeNS "currency" "CURRENCY"
flag :: Nation String
flag = Nation $ makeNS "flag" "FLAG"
banner :: Nation String
banner = Nation $ makeNS "banner" "BANNER"
banners :: Nation [String]
banners = Nation $ makeNS' (shard "banners") parse
where
parse _ root
| Just parent <- findChild (unqual "BANNERS") root
= map strContent $ elChildren parent
| otherwise
= error "could not find banner codes"
censusscore :: Nation (Integer, Double)
censusscore = Nation $ makeNS' (shard "censusscore") parse
where
parse q root
| Just (i, _) <- MultiSet.minView $ MultiSet.difference response request
, Just x <- lookup i censusScores
= (i, x)
| otherwise
= error "could not find census score"
where
censusScores = extractCensusScores root
request = MultiSet.mapMaybe id . MultiSet.fromSet $
queryShards q Map.! "censusscore"
response = MultiSet.fromList $ map fst censusScores
censusscore' :: Integer -> Nation Double
censusscore' i = Nation $ makeNS' (shard' "censusscore" i) parse
where
parse _ = fromMaybe (error $ "could not find census " ++ show i) .
lookup i . extractCensusScores
extractCensusScores :: Element -> [(Integer, Double)]
extractCensusScores root = catMaybes [
(,) <$> maybeId <*> maybeValue |
Elem e <- elContent root,
elName e == unqual "CENSUSSCORE",
let maybeId = readMaybe =<< findAttr (unqual "id") e,
let maybeValue = readMaybe $ strContent e ]