{-# OPTIONS_GHC -fwarn-incomplete-patterns  #-}
{-# OPTIONS_GHC -fwarn-missing-methods      #-}
{-# LANGUAGE DeriveDataTypeable             #-}

module Facts.Geography.Countries.Internal.Data ( Country        (..)
                                               , CountryName    (..)
                                               , ISOAlpha2Code  (..)
                                               , ISOAlpha3Code  (..)
                                               , ISOCountryCode (..)
                                               , ISONumericCode (..)
                                               , isoNumericCode
                                               , countries_and_united_nations_names
                                               , countries_and_iso_country_codes
                                               , UNFormalName
                                               , UNShortName
                                               , valid_iso_country_codes
                                               , valid_iso_numeric_codes
                                               , validate_isoNumericCode
                                               ) where

import Data.Data
import Data.Maybe
import Data.Numerals.Decimal
import Data.Typeable

import Prelude hiding (GT, LT)

import Facts.Utility.Templates


-- | The type of \"countries\" includes sovereign nations and other \"areas of geographical interest\",
--   as defined by the United Nations, whose definition was adopted by ISO.

data Country = Afghanistan
             | AlandIslands
             | Albania
             | Algeria
             | AmericanSamoa
             | Andorra
             | Angola
             | Anguilla
             | Antarctica
             | AntiguaAndBarbuda
             | Argentina
             | Armenia
             | Aruba
             | Australia
             | Austria
             | Azerbaijan
             | Bahamas
             | Bahrain
             | Bangladesh
             | Barbados
             | Belarus
             | Belgium
             | Belize
             | Benin
             | Bermuda
             | Bhutan
             | Bolivia
             | BosniaAndHerzegovina
             | Botswana
             | BouvetIsland
             | Brazil
             | BritishIndianOceanTerritory
             | BruneiDarussalam
             | Bulgaria
             | BurkinaFaso
             | Burundi
             | Cambodia
             | Cameroon
             | Canada
             | CapeVerde
             | CaymanIslands
             | CentralAfricanRepublic
             | Chad
             | Chile
             | China
             | ChristmasIsland
             | CocosKeelingIslands
             | Colombia
             | Comoros
             | Congo
             | DemocraticRepublicOfCongo
             | CookIslands
             | CostaRica
             | CoteDIvoire
             | Croatia
             | Cuba
             | Cyprus
             | CzechRepublic
             | Denmark
             | Djibouti
             | Dominica
             | DominicanRepublic
             | Ecuador
             | Egypt
             | ElSalvador
             | EquatorialGuinea
             | Eritrea
             | Estonia
             | Ethiopia
             | FalklandIslands
             | FaroeIslands
             | Fiji
             | Finland
             | France
             | FrenchGuiana
             | FrenchPolynesia
             | FrenchSouthernTerritories
             | Gabon
             | Gambia
             | Georgia
             | Germany
             | Ghana
             | Gibraltar
             | Greece
             | Greenland
             | Grenada
             | Guadeloupe
             | Guam
             | Guatemala
             | Guernsey
             | Guinea
             | GuineaBissau
             | Guyana
             | Haiti
             | HeardIslandAndMcDonaldIslands
             | HolySee
             | Honduras
             | HongKong
             | Hungary
             | Iceland
             | India
             | Indonesia
             | Iran
             | Iraq
             | Ireland
             | IsleOfMan
             | Israel
             | Italy
             | Jamaica
             | Japan
             | Jersey
             | Jordan
             | Kazakhstan
             | Kenya
             | Kiribati
             | NorthKorea
             | SouthKorea
             | Kuwait
             | Kyrgyzstan
             | Laos
             | Latvia
             | Lebanon
             | Lesotho
             | Liberia
             | Libya
             | Liechtenstein
             | Lithuania
             | Luxembourg
             | Macao
             | Macedonia
             | Madagascar
             | Malawi
             | Malaysia
             | Maldives
             | Mali
             | Malta
             | MarshallIslands
             | Martinique
             | Mauritania
             | Mauritius
             | Mayotte
             | Mexico
             | Micronesia
             | Moldova
             | Monaco
             | Mongolia
             | Montenegro
             | Montserrat
             | Morocco
             | Mozambique
             | Myanmar
             | Namibia
             | Nauru
             | Nepal
             | Netherlands
             | NetherlandsAntilles
             | NewCaledonia
             | NewZealand
             | Nicaragua
             | Niger
             | Nigeria
             | Niue
             | NorfolkIsland
             | NorthernMarianaIslands
             | Norway
             | Oman
             | Pakistan
             | Palau
             | Palestinine
             | Panama
             | PapuaNewGuinea
             | Paraguay
             | Peru
             | Philippines
             | Pitcairn
             | Poland
             | Portugal
             | PuertoRico
             | Qatar
             | Reunion
             | Romania
             | RussianFederation
             | Rwanda
             | SaintBarthelemy
             | SaintHelenaAscensionAndTristanDaCunha
             | SaintKittsAndNevis
             | SaintLucia
             | SaintMartin
             | SaintPierreAndMiquelon
             | SaintVincentAndTheGrenadines
             | Samoa
             | SanMarino
             | SaoTomeAndPrincipe
             | SaudiArabia
             | Senegal
             | Serbia
             | Seychelles
             | SierraLeone
             | Singapore
             | Slovakia
             | Slovenia
             | SolomonIslands
             | Somalia
             | SouthAfrica
             | SouthGeorgiaAndtheSouthSandwichIslands
             | Spain
             | SriLanka
             | Sudan
             | Suriname
             | SvalbardAndJanMayen
             | Swaziland
             | Sweden
             | Switzerland
             | Syria
             | Taiwan
             | Tajikistan
             | Tanzania
             | Thailand
             | TimorLeste
             | Togo
             | Tokelau
             | Tonga
             | TrinidadAndTobago
             | Tunisia
             | Turkey
             | Turkmenistan
             | TurksAndCaicosIslands
             | Tuvalu
             | Uganda
             | Ukraine
             | UnitedArabEmirates
             | UnitedKingdom
             | UnitedStates
             | UnitedStatesMinorOutlyingIslands
             | Uruguay
             | Uzbekistan
             | Vanuatu
             | Venezuela
             | VietNam
             | BritishVirginIslands
             | USVirginIslands
             | WallisAndFutuna
             | WesternSahara
             | Yemen
             | Zambia
             | Zimbabwe
             deriving (Data, Enum, Eq, Ord, Typeable)

data ISOAlpha2Code = AF
                   | AX
                   | AL
                   | DZ
                   | AS
                   | AD
                   | AO
                   | AI
                   | AQ
                   | AG
                   | AR
                   | AM
                   | AW
                   | AU
                   | AT
                   | AZ
                   | BS
                   | BH
                   | BD
                   | BB
                   | BY
                   | BE
                   | BZ
                   | BJ
                   | BM
                   | BT
                   | BO
                   | BA
                   | BW
                   | BV
                   | BR
                   | IO
                   | BN
                   | BG
                   | BF
                   | BI
                   | KH
                   | CM
                   | CA
                   | CV
                   | KY
                   | CF
                   | TD
                   | CL
                   | CN
                   | CX
                   | CC
                   | CO
                   | KM
                   | CG
                   | CD
                   | CK
                   | CR
                   | CI
                   | HR
                   | CU
                   | CY
                   | CZ
                   | DK
                   | DJ
                   | DM
                   | DO
                   | EC
                   | EG
                   | SV
                   | GQ
                   | ER
                   | EE
                   | ET
                   | FK
                   | FO
                   | FJ
                   | FI
                   | FR
                   | GF
                   | PF
                   | TF
                   | GA
                   | GM
                   | GE
                   | DE
                   | GH
                   | GI
                   | GR
                   | GL
                   | GD
                   | GP
                   | GU
                   | GT
                   | GG
                   | GN
                   | GW
                   | GY
                   | HT
                   | HM
                   | VA
                   | HN
                   | HK
                   | HU
                   | IS
                   | IN
                   | ID
                   | IR
                   | IQ
                   | IE
                   | IM
                   | IL
                   | IT
                   | JM
                   | JP
                   | JE
                   | JO
                   | KZ
                   | KE
                   | KI
                   | KP
                   | KR
                   | KW
                   | KG
                   | LA
                   | LV
                   | LB
                   | LS
                   | LR
                   | LY
                   | LI
                   | LT
                   | LU
                   | MO
                   | MK
                   | MG
                   | MW
                   | MY
                   | MV
                   | ML
                   | MT
                   | MH
                   | MQ
                   | MR
                   | MU
                   | YT
                   | MX
                   | FM
                   | MD
                   | MC
                   | MN
                   | ME
                   | MS
                   | MA
                   | MZ
                   | MM
                   | NA
                   | NR
                   | NP
                   | NL
                   | AN
                   | NC
                   | NZ
                   | NI
                   | NE
                   | NG
                   | NU
                   | NF
                   | MP
                   | NO
                   | OM
                   | PK
                   | PW
                   | PS
                   | PA
                   | PG
                   | PY
                   | PE
                   | PH
                   | PN
                   | PL
                   | PT
                   | PR
                   | QA
                   | RE
                   | RO
                   | RU
                   | RW
                   | BL
                   | SH
                   | KN
                   | LC
                   | MF
                   | PM
                   | VC
                   | WS
                   | SM
                   | ST
                   | SA
                   | SN
                   | RS
                   | SC
                   | SL
                   | SG
                   | SK
                   | SI
                   | SB
                   | SO
                   | ZA
                   | GS
                   | ES
                   | LK
                   | SD
                   | SR
                   | SJ
                   | SZ
                   | SE
                   | CH
                   | SY
                   | TW
                   | TJ
                   | TZ
                   | TH
                   | TL
                   | TG
                   | TK
                   | TO
                   | TT
                   | TN
                   | TR
                   | TM
                   | TC
                   | TV
                   | UG
                   | UA
                   | AE
                   | GB
                   | US
                   | UM
                   | UY
                   | UZ
                   | VU
                   | VE
                   | VN
                   | VG
                   | VI
                   | WF
                   | EH
                   | YE
                   | ZM
                   | ZW
                   deriving (Data, Enum, Eq, Ord, Show, Typeable)

data ISOAlpha3Code = AFG
                   | ALA
                   | ALB
                   | DZA
                   | ASM
                   | AND
                   | AGO
                   | AIA
                   | ATA
                   | ATG
                   | ARG
                   | ARM
                   | ABW
                   | AUS
                   | AUT
                   | AZE
                   | BHS
                   | BHR
                   | BGD
                   | BRB
                   | BLR
                   | BEL
                   | BLZ
                   | BEN
                   | BMU
                   | BTN
                   | BOL
                   | BIH
                   | BWA
                   | BVT
                   | BRA
                   | IOT
                   | BRN
                   | BGR
                   | BFA
                   | BDI
                   | KHM
                   | CMR
                   | CAN
                   | CPV
                   | CYM
                   | CAF
                   | TCD
                   | CHL
                   | CHN
                   | CXR
                   | CCK
                   | COL
                   | COM
                   | COG
                   | COD
                   | COK
                   | CRI
                   | CIV
                   | HRV
                   | CUB
                   | CYP
                   | CZE
                   | DNK
                   | DJI
                   | DMA
                   | DOM
                   | ECU
                   | EGY
                   | SLV
                   | GNQ
                   | ERI
                   | EST
                   | ETH
                   | FLK
                   | FRO
                   | FJI
                   | FIN
                   | FRA
                   | GUF
                   | PYF
                   | ATF
                   | GAB
                   | GMB
                   | GEO
                   | DEU
                   | GHA
                   | GIB
                   | GRC
                   | GRL
                   | GRD
                   | GLP
                   | GUM
                   | GTM
                   | GGY
                   | GIN
                   | GNB
                   | GUY
                   | HTI
                   | HMD
                   | VAT
                   | HND
                   | HKG
                   | HUN
                   | ISL
                   | IND
                   | IDN
                   | IRN
                   | IRQ
                   | IRL
                   | IMN
                   | ISR
                   | ITA
                   | JAM
                   | JPN
                   | JEY
                   | JOR
                   | KAZ
                   | KEN
                   | KIR
                   | PRK
                   | KOR
                   | KWT
                   | KGZ
                   | LAO
                   | LVA
                   | LBN
                   | LSO
                   | LBR
                   | LBY
                   | LIE
                   | LTU
                   | LUX
                   | MAC
                   | MKD
                   | MDG
                   | MWI
                   | MYS
                   | MDV
                   | MLI
                   | MLT
                   | MHL
                   | MTQ
                   | MRT
                   | MUS
                   | MYT
                   | MEX
                   | FSM
                   | MDA
                   | MCO
                   | MNG
                   | MNE
                   | MSR
                   | MAR
                   | MOZ
                   | MMR
                   | NAM
                   | NRU
                   | NPL
                   | NLD
                   | ANT
                   | NCL
                   | NZL
                   | NIC
                   | NER
                   | NGA
                   | NIU
                   | NFK
                   | MNP
                   | NOR
                   | OMN
                   | PAK
                   | PLW
                   | PSE
                   | PAN
                   | PNG
                   | PRY
                   | PER
                   | PHL
                   | PCN
                   | POL
                   | PRT
                   | PRI
                   | QAT
                   | REU
                   | ROU
                   | RUS
                   | RWA
                   | BLM
                   | SHN
                   | KNA
                   | LCA
                   | MAF
                   | SPM
                   | VCT
                   | WSM
                   | SMR
                   | STP
                   | SAU
                   | SEN
                   | SRB
                   | SYC
                   | SLE
                   | SGP
                   | SVK
                   | SVN
                   | SLB
                   | SOM
                   | ZAF
                   | SGS
                   | ESP
                   | LKA
                   | SDN
                   | SUR
                   | SJM
                   | SWZ
                   | SWE
                   | CHE
                   | SYR
                   | TWN
                   | TJK
                   | TZA
                   | THA
                   | TLS
                   | TGO
                   | TKL
                   | TON
                   | TTO
                   | TUN
                   | TUR
                   | TKM
                   | TCA
                   | TUV
                   | UGA
                   | UKR
                   | ARE
                   | GBR
                   | USA
                   | UMI
                   | URY
                   | UZB
                   | VUT
                   | VEN
                   | VNM
                   | VGB
                   | VIR
                   | WLF
                   | ESH
                   | YEM
                   | ZMB
                   | ZWE
                   deriving (Data, Eq, Ord, Show, Typeable)



data ISONumericCode = ISONumericCode [DecimalDigit]
                    deriving (Data, Eq, Ord, Typeable)

instance Show ISONumericCode where
         show (ISONumericCode digits) = concatMap (show . decimal_digit_to_integral) digits

-- | A smart constructor to turn 'Integer's into 'ISONumericCode's.  Note that the space of ISO-3166-1
--   numeric codes has many reserved or otherwise unused codes.  This constructor does not verify that
--   its input is a valid ISO-3166-1 country code, it merely constructs a 
isoNumericCode :: Integer -> ISONumericCode
isoNumericCode n | n < 10       = ISONumericCode $ Zero:Zero:(integral_to_digits n)
                 | n < 100      = ISONumericCode $ Zero     :(integral_to_digits n)
                 | otherwise    = ISONumericCode $           (integral_to_digits n)


data ISOCountryCode = ISOCountryCode { isoAlpha2  :: ISOAlpha2Code
                                     , isoAlpha3  :: ISOAlpha3Code
                                     , isoNumeric :: ISONumericCode
                                     } deriving (Data, Eq, Ord, Show, Typeable)



-- | 'countries_and_iso_country_codes' represents the bijection between 'Country's and 
--    their 'ISOCountryCode's.
countries_and_iso_country_codes :: [ (Country, ISOCountryCode) ]
countries_and_iso_country_codes =

        [ ( Afghanistan	                           , ISOCountryCode  AF     AFG	    (isoNumericCode 004) )
        , ( AlandIslands	                       , ISOCountryCode  AX	    ALA	    (isoNumericCode 248) )
        , ( Albania	                               , ISOCountryCode  AL	    ALB	    (isoNumericCode 008) )
        , ( Algeria	                               , ISOCountryCode  DZ	    DZA	    (isoNumericCode 012) )
        , ( AmericanSamoa	                       , ISOCountryCode  AS	    ASM	    (isoNumericCode 016) )
        , ( Andorra	                               , ISOCountryCode  AD	    AND	    (isoNumericCode 020) )
        , ( Angola	                               , ISOCountryCode  AO	    AGO	    (isoNumericCode 024) )
        , ( Anguilla	                           , ISOCountryCode  AI	    AIA	    (isoNumericCode 660) )
        , ( Antarctica	                           , ISOCountryCode  AQ	    ATA	    (isoNumericCode 010) )
        , ( AntiguaAndBarbuda	                   , ISOCountryCode  AG	    ATG	    (isoNumericCode 028) )
        , ( Argentina	                           , ISOCountryCode  AR	    ARG	    (isoNumericCode 032) )
        , ( Armenia	                               , ISOCountryCode  AM	    ARM	    (isoNumericCode 051) )
        , ( Aruba	                               , ISOCountryCode  AW	    ABW	    (isoNumericCode 533) )
        , ( Australia                              , ISOCountryCode  AU	    AUS	    (isoNumericCode 036) )
        , ( Austria	                               , ISOCountryCode  AT	    AUT	    (isoNumericCode 040) )
        , ( Azerbaijan	                           , ISOCountryCode  AZ	    AZE	    (isoNumericCode 031) )
        , ( Bahamas	                               , ISOCountryCode  BS	    BHS	    (isoNumericCode 044) )
        , ( Bahrain	                               , ISOCountryCode  BH	    BHR	    (isoNumericCode 048) )
        , ( Bangladesh	                           , ISOCountryCode  BD	    BGD	    (isoNumericCode 050) )
        , ( Barbados	                           , ISOCountryCode  BB	    BRB	    (isoNumericCode 052) )
        , ( Belarus	                               , ISOCountryCode  BY	    BLR	    (isoNumericCode 112) )
        , ( Belgium	                               , ISOCountryCode  BE	    BEL	    (isoNumericCode 056) )
        , ( Belize	                               , ISOCountryCode  BZ	    BLZ	    (isoNumericCode 084) )
        , ( Benin	                               , ISOCountryCode  BJ	    BEN	    (isoNumericCode 204) )
        , ( Bermuda	                               , ISOCountryCode  BM	    BMU	    (isoNumericCode 060) )
        , ( Bhutan	                               , ISOCountryCode  BT	    BTN	    (isoNumericCode 064) )
        , ( Bolivia	                               , ISOCountryCode  BO	    BOL	    (isoNumericCode 068) )
        , ( BosniaAndHerzegovina	               , ISOCountryCode  BA	    BIH	    (isoNumericCode 070) )
        , ( Botswana	                           , ISOCountryCode  BW	    BWA	    (isoNumericCode 072) )
        , ( BouvetIsland	                       , ISOCountryCode  BV	    BVT	    (isoNumericCode 074) )
        , ( Brazil	                               , ISOCountryCode  BR	    BRA	    (isoNumericCode 076) )
        , ( BritishIndianOceanTerritory	           , ISOCountryCode  IO	    IOT	    (isoNumericCode 086) )
        , ( BruneiDarussalam	                   , ISOCountryCode  BN	    BRN	    (isoNumericCode 096) )
        , ( Bulgaria	                           , ISOCountryCode  BG	    BGR	    (isoNumericCode 100) )
        , ( BurkinaFaso	                           , ISOCountryCode  BF	    BFA	    (isoNumericCode 854) )
        , ( Burundi	                               , ISOCountryCode  BI	    BDI	    (isoNumericCode 108) )
        , ( Cambodia	                           , ISOCountryCode  KH	    KHM	    (isoNumericCode 116) )
        , ( Cameroon	                           , ISOCountryCode  CM	    CMR	    (isoNumericCode 120) )
        , ( Canada	                               , ISOCountryCode  CA	    CAN	    (isoNumericCode 124) )
        , ( CapeVerde	                           , ISOCountryCode  CV	    CPV	    (isoNumericCode 132) )
        , ( CaymanIslands	                       , ISOCountryCode  KY	    CYM	    (isoNumericCode 136) )
        , ( CentralAfricanRepublic	               , ISOCountryCode  CF	    CAF	    (isoNumericCode 140) )
        , ( Chad	                               , ISOCountryCode  TD	    TCD	    (isoNumericCode 148) )
        , ( Chile	                               , ISOCountryCode  CL	    CHL	    (isoNumericCode 152) )
        , ( China	                               , ISOCountryCode  CN	    CHN	    (isoNumericCode 156) )
        , ( ChristmasIsland	                       , ISOCountryCode  CX	    CXR	    (isoNumericCode 162) )
        , ( CocosKeelingIslands	                   , ISOCountryCode  CC	    CCK	    (isoNumericCode 166) )
        , ( Colombia	                           , ISOCountryCode  CO	    COL	    (isoNumericCode 170) )
        , ( Comoros	                               , ISOCountryCode  KM	    COM	    (isoNumericCode 174) )
        , ( Congo	                               , ISOCountryCode  CG	    COG	    (isoNumericCode 178) )
        , ( DemocraticRepublicOfCongo              , ISOCountryCode  CD	    COD	    (isoNumericCode 180) )
        , ( CookIslands	                           , ISOCountryCode  CK	    COK	    (isoNumericCode 184) )
        , ( CostaRica	                           , ISOCountryCode  CR	    CRI	    (isoNumericCode 188) )
        , ( CoteDIvoire	                           , ISOCountryCode  CI	    CIV	    (isoNumericCode 384) )
        , ( Croatia	                               , ISOCountryCode  HR	    HRV	    (isoNumericCode 191) )
        , ( Cuba	                               , ISOCountryCode  CU	    CUB	    (isoNumericCode 192) )
        , ( Cyprus	                               , ISOCountryCode  CY	    CYP	    (isoNumericCode 196) )
        , ( CzechRepublic	                       , ISOCountryCode  CZ	    CZE	    (isoNumericCode 203) )
        , ( Denmark	                               , ISOCountryCode  DK	    DNK	    (isoNumericCode 208) )
        , ( Djibouti	                           , ISOCountryCode  DJ	    DJI	    (isoNumericCode 262) )
        , ( Dominica	                           , ISOCountryCode  DM	    DMA	    (isoNumericCode 212) )
        , ( DominicanRepublic	                   , ISOCountryCode  DO	    DOM	    (isoNumericCode 214) )
        , ( Ecuador	                               , ISOCountryCode  EC	    ECU	    (isoNumericCode 218) )
        , ( Egypt	                               , ISOCountryCode  EG     EGY     (isoNumericCode 818) )
        , ( ElSalvador	                           , ISOCountryCode  SV	    SLV	    (isoNumericCode 222) )
        , ( EquatorialGuinea	                   , ISOCountryCode  GQ	    GNQ	    (isoNumericCode 226) )
        , ( Eritrea	                               , ISOCountryCode  ER	    ERI	    (isoNumericCode 232) )
        , ( Estonia	                               , ISOCountryCode  EE	    EST	    (isoNumericCode 233) )
        , ( Ethiopia	                           , ISOCountryCode  ET	    ETH	    (isoNumericCode 231) )
        , ( FalklandIslands          	           , ISOCountryCode  FK	    FLK	    (isoNumericCode 238) )
        , ( FaroeIslands	                       , ISOCountryCode  FO	    FRO	    (isoNumericCode 234) )
        , ( Fiji	                               , ISOCountryCode  FJ	    FJI	    (isoNumericCode 242) )
        , ( Finland	                               , ISOCountryCode  FI	    FIN	    (isoNumericCode 246) )
        , ( France	                               , ISOCountryCode  FR	    FRA	    (isoNumericCode 250) )
        , ( FrenchGuiana	                       , ISOCountryCode  GF	    GUF	    (isoNumericCode 254) )
        , ( FrenchPolynesia	                       , ISOCountryCode  PF	    PYF	    (isoNumericCode 258) )
        , ( FrenchSouthernTerritories	           , ISOCountryCode  TF	    ATF	    (isoNumericCode 260) )
        , ( Gabon	                               , ISOCountryCode  GA	    GAB	    (isoNumericCode 266) )
        , ( Gambia	                               , ISOCountryCode  GM	    GMB	    (isoNumericCode 270) )
        , ( Georgia	                               , ISOCountryCode  GE	    GEO	    (isoNumericCode 268) )
        , ( Germany	                               , ISOCountryCode  DE	    DEU	    (isoNumericCode 276) )
        , ( Ghana	                               , ISOCountryCode  GH	    GHA	    (isoNumericCode 288) )
        , ( Gibraltar	                           , ISOCountryCode  GI	    GIB	    (isoNumericCode 292) )
        , ( Greece	                               , ISOCountryCode  GR	    GRC	    (isoNumericCode 300) )
        , ( Greenland	                           , ISOCountryCode  GL	    GRL	    (isoNumericCode 304) )
        , ( Grenada	                               , ISOCountryCode  GD	    GRD	    (isoNumericCode 308) )
        , ( Guadeloupe	                           , ISOCountryCode  GP	    GLP	    (isoNumericCode 312) )
        , ( Guam	                               , ISOCountryCode  GU	    GUM	    (isoNumericCode 316) )
        , ( Guatemala	                           , ISOCountryCode  GT	    GTM	    (isoNumericCode 320) )
        , ( Guernsey	                           , ISOCountryCode  GG	    GGY	    (isoNumericCode 831) )
        , ( Guinea	                               , ISOCountryCode  GN	    GIN	    (isoNumericCode 324) )
        , ( GuineaBissau	                       , ISOCountryCode  GW	    GNB	    (isoNumericCode 624) )
        , ( Guyana	                               , ISOCountryCode  GY	    GUY	    (isoNumericCode 328) )
        , ( Haiti	                               , ISOCountryCode  HT	    HTI	    (isoNumericCode 332) )
        , ( HeardIslandAndMcDonaldIslands	       , ISOCountryCode  HM	    HMD	    (isoNumericCode 334) )
        , ( HolySee                       	       , ISOCountryCode  VA	    VAT	    (isoNumericCode 336) )
        , ( Honduras	                           , ISOCountryCode  HN	    HND	    (isoNumericCode 340) )
        , ( HongKong	                           , ISOCountryCode  HK	    HKG	    (isoNumericCode 344) )
        , ( Hungary	                               , ISOCountryCode  HU	    HUN	    (isoNumericCode 348) )
        , ( Iceland	                               , ISOCountryCode  IS	    ISL	    (isoNumericCode 352) )
        , ( India	                               , ISOCountryCode  IN	    IND	    (isoNumericCode 356) )
        , ( Indonesia	                           , ISOCountryCode  ID	    IDN	    (isoNumericCode 360) )
        , ( Iran                                   , ISOCountryCode  IR	    IRN	    (isoNumericCode 364) )
        , ( Iraq	                               , ISOCountryCode  IQ	    IRQ	    (isoNumericCode 368) )
        , ( Ireland	                               , ISOCountryCode  IE	    IRL	    (isoNumericCode 372) )
        , ( IsleOfMan	                           , ISOCountryCode  IM	    IMN	    (isoNumericCode 833) )
        , ( Israel	                               , ISOCountryCode  IL	    ISR	    (isoNumericCode 376) )
        , ( Italy	                               , ISOCountryCode  IT	    ITA	    (isoNumericCode 380) )
        , ( Jamaica	                               , ISOCountryCode  JM	    JAM	    (isoNumericCode 388) )
        , ( Japan	                               , ISOCountryCode  JP	    JPN	    (isoNumericCode 392) )
        , ( Jersey	                               , ISOCountryCode  JE	    JEY	    (isoNumericCode 832) )
        , ( Jordan	                               , ISOCountryCode  JO	    JOR	    (isoNumericCode 400) )
        , ( Kazakhstan	                           , ISOCountryCode  KZ	    KAZ	    (isoNumericCode 398) )
        , ( Kenya	                               , ISOCountryCode  KE	    KEN	    (isoNumericCode 404) )
        , ( Kiribati	                           , ISOCountryCode  KI	    KIR	    (isoNumericCode 296) )
        , ( NorthKorea                             , ISOCountryCode  KP	    PRK	    (isoNumericCode 408) )
        , ( SouthKorea                             , ISOCountryCode  KR	    KOR	    (isoNumericCode 410) )
        , ( Kuwait	                               , ISOCountryCode  KW	    KWT	    (isoNumericCode 414) )
        , ( Kyrgyzstan	                           , ISOCountryCode  KG	    KGZ	    (isoNumericCode 417) )
        , ( Laos                         	       , ISOCountryCode  LA	    LAO	    (isoNumericCode 418) )
        , ( Latvia	                               , ISOCountryCode  LV	    LVA	    (isoNumericCode 428) )
        , ( Lebanon	                               , ISOCountryCode  LB	    LBN	    (isoNumericCode 422) )
        , ( Lesotho	                               , ISOCountryCode  LS	    LSO	    (isoNumericCode 426) )
        , ( Liberia	                               , ISOCountryCode  LR	    LBR	    (isoNumericCode 430) )
        , ( Libya                  	               , ISOCountryCode  LY	    LBY	    (isoNumericCode 434) )
        , ( Liechtenstein	                       , ISOCountryCode  LI	    LIE	    (isoNumericCode 438) )
        , ( Lithuania	                           , ISOCountryCode  LT	    LTU	    (isoNumericCode 440) )
        , ( Luxembourg	                           , ISOCountryCode  LU	    LUX	    (isoNumericCode 442) )
        , ( Macao	                               , ISOCountryCode  MO	    MAC	    (isoNumericCode 446) )
        , ( Macedonia                              , ISOCountryCode  MK	    MKD	    (isoNumericCode 807) )
        , ( Madagascar	                           , ISOCountryCode  MG	    MDG	    (isoNumericCode 450) )
        , ( Malawi	                               , ISOCountryCode  MW	    MWI	    (isoNumericCode 454) )
        , ( Malaysia	                           , ISOCountryCode  MY	    MYS	    (isoNumericCode 458) )
        , ( Maldives	                           , ISOCountryCode  MV	    MDV	    (isoNumericCode 462) )
        , ( Mali	                               , ISOCountryCode  ML	    MLI	    (isoNumericCode 466) )
        , ( Malta	                               , ISOCountryCode  MT	    MLT	    (isoNumericCode 470) )
        , ( MarshallIslands	                       , ISOCountryCode  MH	    MHL	    (isoNumericCode 584) )
        , ( Martinique	                           , ISOCountryCode  MQ	    MTQ	    (isoNumericCode 474) )
        , ( Mauritania	                           , ISOCountryCode  MR	    MRT	    (isoNumericCode 478) )
        , ( Mauritius	                           , ISOCountryCode  MU	    MUS	    (isoNumericCode 480) )
        , ( Mayotte	                               , ISOCountryCode  YT	    MYT	    (isoNumericCode 175) )
        , ( Mexico	                               , ISOCountryCode  MX	    MEX	    (isoNumericCode 484) )
        , ( Micronesia                             , ISOCountryCode  FM	    FSM	    (isoNumericCode 583) )
        , ( Moldova                                , ISOCountryCode  MD	    MDA	    (isoNumericCode 498) )
        , ( Monaco	                               , ISOCountryCode  MC	    MCO	    (isoNumericCode 492) )
        , ( Mongolia	                           , ISOCountryCode  MN	    MNG	    (isoNumericCode 496) )
        , ( Montenegro	                           , ISOCountryCode  ME	    MNE	    (isoNumericCode 499) )
        , ( Montserrat	                           , ISOCountryCode  MS	    MSR	    (isoNumericCode 500) )
        , ( Morocco	                               , ISOCountryCode  MA	    MAR	    (isoNumericCode 504) )
        , ( Mozambique	                           , ISOCountryCode  MZ	    MOZ	    (isoNumericCode 508) )
        , ( Myanmar	                               , ISOCountryCode  MM	    MMR	    (isoNumericCode 104) )
        , ( Namibia	                               , ISOCountryCode  NA	    NAM	    (isoNumericCode 516) )
        , ( Nauru	                               , ISOCountryCode  NR	    NRU	    (isoNumericCode 520) )
        , ( Nepal	                               , ISOCountryCode  NP	    NPL	    (isoNumericCode 524) )
        , ( Netherlands	                           , ISOCountryCode  NL	    NLD	    (isoNumericCode 528) )
        , ( NetherlandsAntilles	                   , ISOCountryCode  AN	    ANT	    (isoNumericCode 530) )
        , ( NewCaledonia	                       , ISOCountryCode  NC	    NCL	    (isoNumericCode 540) )
        , ( NewZealand	                           , ISOCountryCode  NZ	    NZL	    (isoNumericCode 554) )
        , ( Nicaragua	                           , ISOCountryCode  NI	    NIC	    (isoNumericCode 558) )
        , ( Niger	                               , ISOCountryCode  NE	    NER	    (isoNumericCode 562) )
        , ( Nigeria	                               , ISOCountryCode  NG	    NGA	    (isoNumericCode 566) )
        , ( Niue	                               , ISOCountryCode  NU	    NIU	    (isoNumericCode 570) )
        , ( NorfolkIsland	                       , ISOCountryCode  NF	    NFK	    (isoNumericCode 574) )
        , ( NorthernMarianaIslands	               , ISOCountryCode  MP	    MNP	    (isoNumericCode 580) )
        , ( Norway	                               , ISOCountryCode  NO	    NOR	    (isoNumericCode 578) )
        , ( Oman	                               , ISOCountryCode  OM	    OMN	    (isoNumericCode 512) )
        , ( Pakistan	                           , ISOCountryCode  PK	    PAK	    (isoNumericCode 586) )
        , ( Palau	                               , ISOCountryCode  PW	    PLW	    (isoNumericCode 585) )
        , ( Palestinine                  	       , ISOCountryCode  PS	    PSE	    (isoNumericCode 275) )
        , ( Panama	                               , ISOCountryCode  PA	    PAN	    (isoNumericCode 591) )
        , ( PapuaNewGuinea	                       , ISOCountryCode  PG	    PNG	    (isoNumericCode 598) )
        , ( Paraguay	                           , ISOCountryCode  PY	    PRY	    (isoNumericCode 600) )
        , ( Peru	                               , ISOCountryCode  PE	    PER	    (isoNumericCode 604) )
        , ( Philippines	                           , ISOCountryCode  PH	    PHL	    (isoNumericCode 608) )
        , ( Pitcairn	                           , ISOCountryCode  PN	    PCN	    (isoNumericCode 612) )
        , ( Poland	                               , ISOCountryCode  PL	    POL	    (isoNumericCode 616) )
        , ( Portugal	                           , ISOCountryCode  PT	    PRT	    (isoNumericCode 620) )
        , ( PuertoRico	                           , ISOCountryCode  PR	    PRI	    (isoNumericCode 630) )
        , ( Qatar	                               , ISOCountryCode  QA	    QAT	    (isoNumericCode 634) )
        , ( Reunion	                               , ISOCountryCode  RE	    REU	    (isoNumericCode 638) )
        , ( Romania	                               , ISOCountryCode  RO	    ROU	    (isoNumericCode 642) )
        , ( RussianFederation	                   , ISOCountryCode  RU	    RUS	    (isoNumericCode 643) )
        , ( Rwanda	                               , ISOCountryCode  RW	    RWA	    (isoNumericCode 646) )
        , ( SaintBarthelemy	                       , ISOCountryCode  BL	    BLM	    (isoNumericCode 652) )
        , ( SaintHelenaAscensionAndTristanDaCunha  , ISOCountryCode  SH	    SHN	    (isoNumericCode 654) )
        , ( SaintKittsAndNevis	                   , ISOCountryCode  KN	    KNA	    (isoNumericCode 659) )
        , ( SaintLucia	                           , ISOCountryCode  LC	    LCA	    (isoNumericCode 662) )
        , ( SaintMartin                            , ISOCountryCode  MF	    MAF	    (isoNumericCode 663) )
        , ( SaintPierreAndMiquelon	               , ISOCountryCode  PM	    SPM	    (isoNumericCode 666) )
        , ( SaintVincentAndTheGrenadines	       , ISOCountryCode  VC	    VCT	    (isoNumericCode 670) )
        , ( Samoa	                               , ISOCountryCode  WS	    WSM	    (isoNumericCode 882) )
        , ( SanMarino	                           , ISOCountryCode  SM	    SMR	    (isoNumericCode 674) )
        , ( SaoTomeAndPrincipe	                   , ISOCountryCode  ST	    STP	    (isoNumericCode 678) )
        , ( SaudiArabia	                           , ISOCountryCode  SA	    SAU	    (isoNumericCode 682) )
        , ( Senegal	                               , ISOCountryCode  SN	    SEN	    (isoNumericCode 686) )
        , ( Serbia	                               , ISOCountryCode  RS	    SRB	    (isoNumericCode 688) )
        , ( Seychelles	                           , ISOCountryCode  SC	    SYC	    (isoNumericCode 690) )
        , ( SierraLeone	                           , ISOCountryCode  SL	    SLE	    (isoNumericCode 694) )
        , ( Singapore	                           , ISOCountryCode  SG	    SGP	    (isoNumericCode 702) )
        , ( Slovakia	                           , ISOCountryCode  SK	    SVK	    (isoNumericCode 703) )
        , ( Slovenia	                           , ISOCountryCode  SI	    SVN	    (isoNumericCode 705) )
        , ( SolomonIslands	                       , ISOCountryCode  SB	    SLB	    (isoNumericCode 090) )
        , ( Somalia	                               , ISOCountryCode  SO	    SOM	    (isoNumericCode 706) )
        , ( SouthAfrica	                           , ISOCountryCode  ZA	    ZAF	    (isoNumericCode 710) )
        , ( SouthGeorgiaAndtheSouthSandwichIslands , ISOCountryCode  GS	    SGS	    (isoNumericCode 239) )
        , ( Spain	                               , ISOCountryCode  ES	    ESP	    (isoNumericCode 724) )
        , ( SriLanka	                           , ISOCountryCode  LK	    LKA	    (isoNumericCode 144) )
        , ( Sudan	                               , ISOCountryCode  SD	    SDN	    (isoNumericCode 736) )
        , ( Suriname	                           , ISOCountryCode  SR	    SUR	    (isoNumericCode 740) )
        , ( SvalbardAndJanMayen	                   , ISOCountryCode  SJ	    SJM	    (isoNumericCode 744) )
        , ( Swaziland	                           , ISOCountryCode  SZ	    SWZ	    (isoNumericCode 748) )
        , ( Sweden	                               , ISOCountryCode  SE	    SWE	    (isoNumericCode 752) )
        , ( Switzerland	                           , ISOCountryCode  CH	    CHE	    (isoNumericCode 756) )
        , ( Syria              	                   , ISOCountryCode  SY	    SYR	    (isoNumericCode 760) )
        , ( Taiwan                   	           , ISOCountryCode  TW	    TWN	    (isoNumericCode 158) )
        , ( Tajikistan	                           , ISOCountryCode  TJ	    TJK	    (isoNumericCode 762) )
        , ( Tanzania                 	           , ISOCountryCode  TZ	    TZA	    (isoNumericCode 834) )
        , ( Thailand	                           , ISOCountryCode  TH	    THA	    (isoNumericCode 764) )
        , ( TimorLeste	                           , ISOCountryCode  TL	    TLS	    (isoNumericCode 626) )
        , ( Togo	                               , ISOCountryCode  TG	    TGO	    (isoNumericCode 768) )
        , ( Tokelau	                               , ISOCountryCode  TK	    TKL	    (isoNumericCode 772) )
        , ( Tonga	                               , ISOCountryCode  TO	    TON	    (isoNumericCode 776) )
        , ( TrinidadAndTobago	                   , ISOCountryCode  TT	    TTO	    (isoNumericCode 780) )
        , ( Tunisia	                               , ISOCountryCode  TN	    TUN	    (isoNumericCode 788) )
        , ( Turkey	                               , ISOCountryCode  TR	    TUR	    (isoNumericCode 792) )
        , ( Turkmenistan	                       , ISOCountryCode  TM	    TKM	    (isoNumericCode 795) )
        , ( TurksAndCaicosIslands	               , ISOCountryCode  TC	    TCA	    (isoNumericCode 796) )
        , ( Tuvalu	                               , ISOCountryCode  TV	    TUV	    (isoNumericCode 798) )
        , ( Uganda	                               , ISOCountryCode  UG	    UGA	    (isoNumericCode 800) )
        , ( Ukraine	                               , ISOCountryCode  UA	    UKR	    (isoNumericCode 804) )
        , ( UnitedArabEmirates	                   , ISOCountryCode  AE	    ARE	    (isoNumericCode 784) )
        , ( UnitedKingdom	                       , ISOCountryCode  GB	    GBR	    (isoNumericCode 826) )
        , ( UnitedStates	                       , ISOCountryCode  US	    USA	    (isoNumericCode 840) )
        , ( UnitedStatesMinorOutlyingIslands	   , ISOCountryCode  UM	    UMI	    (isoNumericCode 581) )
        , ( Uruguay	                               , ISOCountryCode  UY	    URY	    (isoNumericCode 858) )
        , ( Uzbekistan                             , ISOCountryCode  UZ	    UZB	    (isoNumericCode 860) )
        , ( Vanuatu	                               , ISOCountryCode  VU	    VUT	    (isoNumericCode 548) )
        , ( Venezuela                        	   , ISOCountryCode  VE	    VEN	    (isoNumericCode 862) )
        , ( VietNam	                               , ISOCountryCode  VN	    VNM	    (isoNumericCode 704) )
        , ( BritishVirginIslands	               , ISOCountryCode  VG	    VGB	    (isoNumericCode 092) )
        , ( USVirginIslands	                       , ISOCountryCode  VI	    VIR	    (isoNumericCode 850) )
        , ( WallisAndFutuna	                       , ISOCountryCode  WF	    WLF	    (isoNumericCode 876) )
        , ( WesternSahara	                       , ISOCountryCode  EH	    ESH	    (isoNumericCode 732) )
        , ( Yemen	                               , ISOCountryCode  YE	    YEM	    (isoNumericCode 887) )
        , ( Zambia	                               , ISOCountryCode  ZM	    ZMB	    (isoNumericCode 894) )
        , ( Zimbabwe	                           , ISOCountryCode  ZW	    ZWE	    (isoNumericCode 716) )
        ]




-- | A \"table\" of 'ISOCountryCode's, each of which is a relation in three values.
--   By construction, these are the only valid ISOCountryCode values. 

valid_iso_country_codes :: [ISOCountryCode]
valid_iso_country_codes = fmap snd countries_and_iso_country_codes

-- | A \"table\" of 'ISONumericCode's, each of which is a relation in three values.
--   By construction, these are the only valid 'ISONumericCode' values. 


valid_iso_numeric_codes :: [ISONumericCode]
valid_iso_numeric_codes = fmap isoNumeric valid_iso_country_codes


validate_isoNumericCode :: ISONumericCode -> Maybe ISONumericCode
validate_isoNumericCode code = if   (code `elem` valid_iso_numeric_codes)
                               then (Just code)
                               else (Nothing)



type UNShortName  = String
type UNFormalName = String


-- | The CountryName type encodes "all" the names for
data CountryName = CountryName { english_short_name  :: UNShortName
                               , english_formal_name :: UNFormalName
                               } deriving (Data, Eq, Ord, Show, Typeable)


-- | These names come either from the United Nations document "Terminology Bulletin Country Names"
--   or "Country and Region Codes for Statistical Use" as described by ISO-3166-1.  This data is naturally
--   tabular, and it is worth keeping in that form despite the extreme width of the textual representation.

countries_and_united_nations_names :: [(Country, CountryName)]
countries_and_united_nations_names =                               --   English Short Name                                  English Formal Name
            [ ( Afghanistan                               , CountryName "Afghanistan"                                       "Islamic Republic of Afghanistan"                      )
            , ( AlandIslands	                          , CountryName "Åland Islands"                                     "Åland Islands"                                        )
            , ( Albania                                   , CountryName "Albania"                                           "Republic of Albania"                                  )
            , ( Algeria                                   , CountryName "Algeria"                                           "People's Democratic Republic of Algeria"              )
            , ( AmericanSamoa                             , CountryName "American Samoa"                                    "American Samoa"                                       )
            , ( Andorra                                   , CountryName "Andorra"                                           "Principality of Andorra"                              )
            , ( Angola                                    , CountryName "Angola"                                            "Republic of Angola"                                   )
            , ( Anguilla                                  , CountryName "Anguilla"                                          "Anguilla"                                             )
            , ( Antarctica                                , CountryName "Antarctica"                                        "Antarctica"                                           )
            , ( AntiguaAndBarbuda	                      , CountryName "Antigua and Barbuda"                               "Antigua and Barbuda"                                  )
            , ( Argentina                                 , CountryName "Argentina"                                         "Argentine Republic"                                   )
            , ( Armenia                                   , CountryName "Armenia"                                           "Republic of Armenia"                                  )
            , ( Aruba                                     , CountryName "Aruba"                                             "Aruba"                                                )
            , ( Australia                                 , CountryName "Australia"                                         "Australia"                                            )
            , ( Austria                                   , CountryName "Austria"                                           "Republic of Austria"                                  )
            , ( Azerbaijan                                , CountryName "Azerbaijan"                                        "Republic of Azerbaijan"                               )
            , ( Bahamas                                   , CountryName "Bahamas"                                           "Commonwealth of the Bahamas"                          )
            , ( Bahrain                                   , CountryName "Bahrain"                                           "Kingdom of Bahrain"                                   )
            , ( Bangladesh                                , CountryName "Bangladesh"                                        "People's Republic of Bangladesh"                      )
            , ( Barbados                                  , CountryName "Barbados"                                          "Barbados"                                             )
            , ( Belarus                                   , CountryName "Belarus"                                           "Republic of Belarus"                                  )
            , ( Belgium                                   , CountryName "Belgium"                                           "Kingdom of Belgium"                                   )
            , ( Belize                                    , CountryName "Belize"                                            "Belize"                                               )
            , ( Benin                                     , CountryName "Benin"                                             "Republic of Benin"                                    )
            , ( Bermuda                                   , CountryName "Bermuda"                                           "Bermuda"                                              )
            , ( Bhutan                                    , CountryName "Bhutan"                                            "Kingdom of Bhutan"                                    )
            , ( Bolivia	                                  , CountryName "Bolivia"                                           "Plurinational State of Bolivia"                       )
            , ( BosniaAndHerzegovina	                  , CountryName "Bosnia and Herzegovina"                            "Bosnia and Herzegovina"                               )
            , ( Botswana                                  , CountryName "Botswana"                                          "Republic of Botswana"                                 )
            , ( BouvetIsland                              , CountryName "Bouvet Island"                                     "Bouvet Island"                                        )
            , ( Brazil                                    , CountryName "Brazil"                                            "Federative Republic of Brazil"                        )
            , ( BritishIndianOceanTerritory               , CountryName "British Indian Ocean Territory"                    "British Indian Ocean Territory"                       )
            , ( BruneiDarussalam                          , CountryName "Brunei Darussalam"                                 "Brunei Darussalam"                                    )
            , ( Bulgaria                                  , CountryName "Bulgaria"                                          "Republic of Bulgaria"                                 )
            , ( BurkinaFaso                               , CountryName "Burkina Faso"                                      "Burkina Faso"                                         )
            , ( Burundi                                   , CountryName "Burundi"                                           "Republic of Burundi"                                  )
            , ( Cambodia                                  , CountryName "Cambodia"                                          "Kingdom of Cambodia"                                  )
            , ( Cameroon                                  , CountryName "Cameroon"                                          "Republic of Cameroon"                                 )
            , ( Canada                                    , CountryName "Canada"                                            "Canada"                                               )
            , ( CapeVerde                                 , CountryName "Cape Verde"                                        "Republic of Cape Verde"                               )
            , ( CaymanIslands                             , CountryName "Cayman Islands"                                    "Cayman Islands"                                       )
            , ( CentralAfricanRepublic                    , CountryName "Central African Republic"                          "Central African Republic"                             )
            , ( Chad                                      , CountryName "Chad"                                              "Republic of Chad"                                     )
            , ( Chile                                     , CountryName "Chile"                                             "Republic of Chile"                                    )
            , ( China                                     , CountryName "China"                                             "People's Republic of China"                           )
            , ( ChristmasIsland                           , CountryName "Christmas Island"                                  "Christmas Island"                                     )
            , ( CocosKeelingIslands	                      , CountryName "Cocos (Keeling) Islands"                           "Cocos (Keeling) Islands"                              )
            , ( Colombia                                  , CountryName "Colombia"                                          "Republic of Colombia"                                 )
            , ( Comoros                                   , CountryName "Comoros"                                           "Union of he Comoros"                                  )
            , ( Congo                                     , CountryName "Congo"                                             "Republic of the Congo"                                )
            , ( DemocraticRepublicOfCongo                 , CountryName "Democratic Republic Of Congo"                      "Democratic Republic of the Congo"                     )
            , ( CookIslands                               , CountryName "Cook Islands"                                      "Cook Islands"                                         )
            , ( CostaRica                                 , CountryName "Costa Rica"                                        "Republic of Costa Rica"                               )
            , ( CoteDIvoire	                              , CountryName "Côte d'Ivoire"                                     "Republic of Côte d'Ivoire"                            )
            , ( Croatia                                   , CountryName "Croatia"                                           "Republic of Croatia"                                  )
            , ( Cuba                                      , CountryName "Cuba"                                              "Republic of Cuba"                                     )
            , ( Cyprus                                    , CountryName "Cyprus"                                            "Republic of Cyprus"                                   )
            , ( CzechRepublic                             , CountryName "Czech Republic"                                    "Czech Republic"                                       )
            , ( Denmark                                   , CountryName "Denmark"                                           "Kingdom of Denmark"                                   )
            , ( Djibouti                                  , CountryName "Djibouti"                                          "Republic of Djibouti"                                 )
            , ( Dominica                                  , CountryName "Dominica"                                          "Commonwealth of Dominica"                             )
            , ( DominicanRepublic                         , CountryName "Dominican Republic"                                "Dominican Republic"                                   )
            , ( Ecuador                                   , CountryName "Ecuador"                                           "Republic of Ecuador"                                  )
            , ( Egypt                                     , CountryName "Egypt"                                             "Arab Republic of Egypt"                               )
            , ( ElSalvador                                , CountryName "El Salvador"                                       "Republic of El Salvador"                              )
            , ( EquatorialGuinea                          , CountryName "Equatorial Guinea"                                 "Republic of Equatorial Guinea"                        )
            , ( Eritrea                                   , CountryName "Eritrea"                                           "Eritrea"                                              )
            , ( Estonia                                   , CountryName "Estonia"                                           "Republic of Estonia"                                  )
            , ( Ethiopia                                  , CountryName "Ethiopia"                                          "Federal Democratic Republic of Ethiopia"              )
            , ( FalklandIslands          	              , CountryName "Falkland Islands"                                  "Falkland Islands (Malvinas)"                          )
            , ( FaroeIslands                              , CountryName "Faroe Islands"                                     "Faroe Islands"                                        )
            , ( Fiji                                      , CountryName "Fiji"                                              "Republic of Fiji Islands"                             )
            , ( Finland                                   , CountryName "Finland"                                           "Republic of Finland"                                  )
            , ( France                                    , CountryName "France"                                            "French Republic"                                      )
            , ( FrenchGuiana                              , CountryName "French Guiana"                                     "French Guiana"                                        )
            , ( FrenchPolynesia                           , CountryName "French Polynesia"                                  "French Polynesia"                                     )
            , ( FrenchSouthernTerritories                 , CountryName "French Southern Territories"                       "French Southern Territories"                          )
            , ( Gabon                                     , CountryName "Gabon"                                             "Gabonese Republic"                                    )
            , ( Gambia                                    , CountryName "Gambia"                                            "Republic of the Gambia"                               )
            , ( Georgia                                   , CountryName "Georgia"                                           "Georgia"                                              )
            , ( Germany                                   , CountryName "Germany"                                           "Federal Republic of Germany"                          )
            , ( Ghana                                     , CountryName "Ghana"                                             "Republic of Ghana"                                    )
            , ( Gibraltar                                 , CountryName "Gibraltar"                                         "Gibraltar"                                            )
            , ( Greece                                    , CountryName "Greece"                                            "Hellenic Republic"                                    )
            , ( Greenland                                 , CountryName "Greenland"                                         "Greenland"                                            )
            , ( Grenada                                   , CountryName "Grenada"                                           "Grenada"                                              )
            , ( Guadeloupe                                , CountryName "Guadeloupe"                                        "Guadeloupe"                                           )
            , ( Guam                                      , CountryName "Guam"                                              "Guam"                                                 )
            , ( Guatemala                                 , CountryName "Guatemala"                                         "Republic of Guatemala"                                )
            , ( Guernsey                                  , CountryName "Guernsey"                                          "Guernsey"                                             )
            , ( Guinea                                    , CountryName "Guinea"                                            "Republic of Guinea"                                   )
            , ( GuineaBissau                              , CountryName "Guinea Bissau"                                     "Republic of Guinea-Bissau"                            )
            , ( Guyana                                    , CountryName "Guyana"                                            "Republic of Guyana"                                   )
            , ( Haiti                                     , CountryName "Haiti"                                             "Republic of Haiti"                                    )
            , ( HeardIslandAndMcDonaldIslands             , CountryName "Heard Island And McDonald Islands"                 "Heard Island And McDonald Islands"                    )
            , ( HolySee                       	          , CountryName "Vatican City"                                      "Holy See"                                             )
            , ( Honduras                                  , CountryName "Honduras"                                          "Republic of Honduras"                                 )
            , ( HongKong                                  , CountryName "Hong Kong"                                         "Hong Kong"                                            )
            , ( Hungary                                   , CountryName "Hungary"                                           "Republic of Hungary"                                  )
            , ( Iceland                                   , CountryName "Iceland"                                           "Republic of Iceland"                                  )
            , ( India                                     , CountryName "India"                                             "Republic of India"                                    )
            , ( Indonesia                                 , CountryName "Indonesia"                                         "Republic of Indonesia"                                )
            , ( Iran                                      , CountryName "Iran"                                              "Islamic Republic of Iran"                             )
            , ( Iraq                                      , CountryName "Iraq"                                              "Republic of Iraq"                                     )
            , ( Ireland                                   , CountryName "Ireland"                                           "Ireland"                                              )
            , ( IsleOfMan                                 , CountryName "Isle Of Man"                                       "Isle Of Man"                                          )
            , ( Israel                                    , CountryName "Israel"                                            "State of Israel"                                      )
            , ( Italy                                     , CountryName "Italy"                                             "Republic of Italy"                                    )
            , ( Jamaica                                   , CountryName "Jamaica"                                           "Jamaica"                                              )
            , ( Japan                                     , CountryName "Japan"                                             "Japan"                                                )
            , ( Jersey                                    , CountryName "Jersey"                                            "Jersey"                                               )
            , ( Jordan                                    , CountryName "Jordan"                                            "Hashemite Kingdom of Jordan"                          )
            , ( Kazakhstan                                , CountryName "Kazakhstan"                                        "Republic of Kazakhstan"                               )
            , ( Kenya                                     , CountryName "Kenya"                                             "Republic of Kenya"                                    )
            , ( Kiribati                                  , CountryName "Kiribati"                                          "Republic of Kiribati"                                 )
            , ( NorthKorea                                , CountryName "North Korea"                                       "Democratic People's Republic of Korea"                )
            , ( SouthKorea                                , CountryName "South Korea"                                       "Republic of Korea"                                    )
            , ( Kuwait                                    , CountryName "Kuwait"                                            "State of Kuwait"                                      )
            , ( Kyrgyzstan                                , CountryName "Kyrgyzstan"                                        "Kyrgyz Republic"                                      )
            , ( Laos                         	          , CountryName "Laos"                                              "Lao People's Democratic Republic"                     )
            , ( Latvia                                    , CountryName "Latvia"                                            "Republic of Latvia"                                   )
            , ( Lebanon                                   , CountryName "Lebanon"                                           "Lebanese Republic"                                    )
            , ( Lesotho                                   , CountryName "Lesotho"                                           "Kingdom of Lesotho"                                   )
            , ( Liberia                                   , CountryName "Liberia"                                           "Republic of Liberia"                                  )
            , ( Libya                  	                  , CountryName "Libya"                                             "Socialist People's Libyan Arab Jamahiriya"            )
            , ( Liechtenstein                             , CountryName "Liechtenstein"                                     "Principality of Liechtenstein"                        )
            , ( Lithuania                                 , CountryName "Lithuania"                                         "Republic of Lithuania"                                )
            , ( Luxembourg                                , CountryName "Luxembourg"                                        "Grand Duchy of Luxembourg"                            )
            , ( Macao                                     , CountryName "Macao"                                             "Macao"                                                )
            , ( Macedonia                                 , CountryName "Macedonia"                                         "The former Yugoslav Republic of Macedonia"            )
            , ( Madagascar                                , CountryName "Madagascar"                                        "Republic of Madagascar"                               )
            , ( Malawi                                    , CountryName "Malawi"                                            "Republic of Malawi"                                   )
            , ( Malaysia                                  , CountryName "Malaysia"                                          "Malaysia"                                             )
            , ( Maldives                                  , CountryName "Maldives"                                          "Republic of Maldives"                                 )
            , ( Mali                                      , CountryName "Mali"                                              "Republic of Mali"                                     )
            , ( Malta                                     , CountryName "Malta"                                             "Republic of Malta"                                    )
            , ( MarshallIslands                           , CountryName "Marshall Islands"                                  "Republic of the Marshall Islands"                     )
            , ( Martinique                                , CountryName "Martinique"                                        "Martinique"                                           )
            , ( Mauritania                                , CountryName "Mauritania"                                        "Mauritania"                                           )
            , ( Mauritius                                 , CountryName "Mauritius"                                         "Republic of Mauritius"                                )
            , ( Mayotte                                   , CountryName "Mayotte"                                           "Mayotte"                                              )
            , ( Mexico                                    , CountryName "Mexico"                                            "United Mexican States"                                )
            , ( Micronesia                                , CountryName "Micronesia"                                        "Federated States of Micronesia"                       )
            , ( Moldova                                   , CountryName "Moldova"                                           "Republic of Moldova"                                  )
            , ( Monaco                                    , CountryName "Monaco"                                            "Principality of Monaco"                               )
            , ( Mongolia                                  , CountryName "Mongolia"                                          "Mongolia"                                             )
            , ( Montenegro                                , CountryName "Montenegro"                                        "Montenegro"                                           )
            , ( Montserrat                                , CountryName "Montserrat"                                        "Montserrat"                                           )
            , ( Morocco                                   , CountryName "Morocco"                                           "Kingdom of Morocco"                                   )
            , ( Mozambique                                , CountryName "Mozambique"                                        "Republic of Mozambique"                               )
            , ( Myanmar                                   , CountryName "Myanmar"                                           "Union of Myanmar"                                     )
            , ( Namibia                                   , CountryName "Namibia"                                           "Republic of Namibia"                                  )
            , ( Nauru                                     , CountryName "Nauru"                                             "Republic of Nauru"                                    )
            , ( Nepal                                     , CountryName "Nepal"                                             "Federal Democratic Republic of Nepal"                 )
            , ( Netherlands                               , CountryName "Netherlands"                                       "Kingdom of the Netherlands"                           )
            , ( NetherlandsAntilles                       , CountryName "Netherlands Antilles"                              "Netherlands Antilles"                                 )
            , ( NewCaledonia                              , CountryName "New Caledonia"                                     "New Caledonia"                                        )
            , ( NewZealand                                , CountryName "New Zealand"                                       "New Zealand"                                          )
            , ( Nicaragua                                 , CountryName "Nicaragua"                                         "Republic of Nicaragua"                                )
            , ( Niger                                     , CountryName "Niger"                                             "Republic of Niger"                                    )
            , ( Nigeria                                   , CountryName "Nigeria"                                           "Federal Republic of Nigeria"                          )
            , ( Niue                                      , CountryName "Niue"                                              "Niue"                                                 )
            , ( NorfolkIsland                             , CountryName "Norfolk Island"                                    "Norfolk Island"                                       )
            , ( NorthernMarianaIslands                    , CountryName "Northern Mariana Islands"                          "Northern Mariana Islands"                             )
            , ( Norway                                    , CountryName "Norway"                                            "Kingdom of Norway"                                    )
            , ( Oman                                      , CountryName "Oman"                                              "Sultanate of Oman"                                    )
            , ( Pakistan                                  , CountryName "Pakistan"                                          "Islamic Republic of Pakistan"                         )
            , ( Palau                                     , CountryName "Palau"                                             "Republic of Palau"                                    )
            , ( Palestinine                  	          , CountryName "Palestine"                                         "Occupied Palestinian Territory"                       )
            , ( Panama                                    , CountryName "Panama"                                            "Republic of Panama"                                   )
            , ( PapuaNewGuinea                            , CountryName "Papua New Guinea"                                  "Papua New Guinea"                                     )
            , ( Paraguay                                  , CountryName "Paraguay"                                          "Republic of Paraguay"                                 )
            , ( Peru                                      , CountryName "Peru"                                              "Republic of Peru"                                     )
            , ( Philippines                               , CountryName "Philippines"                                       "Republic of the Philippines"                          )
            , ( Pitcairn                                  , CountryName "Pitcairn"                                          "Pitcairn"                                             )
            , ( Poland                                    , CountryName "Poland"                                            "Republic of Poland"                                   )
            , ( Portugal                                  , CountryName "Portugal"                                          "Portuguese Republic"                                  )
            , ( PuertoRico                                , CountryName "Puerto Rico"                                       "Puerto Rico"                                          )
            , ( Qatar                                     , CountryName "Qatar"                                             "State of Qatar"                                       )
            , ( Reunion                                   , CountryName "Réunion"                                           "Réunion"                                              )
            , ( Romania                                   , CountryName "Romania"                                           "Romania"                                              )
            , ( RussianFederation                         , CountryName "Russian Federation"                                "Russian Federation"                                   )
            , ( Rwanda                                    , CountryName "Rwanda"                                            "Republic of Rwanda"                                   )
            , ( SaintBarthelemy                           , CountryName "Saint Barthélemy"                                  "Saint Barthélemy"                                     )
            , ( SaintHelenaAscensionAndTristanDaCunha     , CountryName "Saint Helena, Ascension, and Tristan da Cunha"     "Saint Helena, Ascension, and Tristan da Cunha"        )
            , ( SaintKittsAndNevis                        , CountryName "Saint Kitts And Nevis"                             "Saint Kitts And Nevis"                                )
            , ( SaintLucia                                , CountryName "Saint Lucia"                                       "Saint Lucia"                                          )
            , ( SaintMartin                               , CountryName "Saint Martin"                                      "Saint Martin"                                         )
            , ( SaintPierreAndMiquelon	                  , CountryName "Saint Pierre and Miquelon"                         "Saint Pierre and Miquelon"                            )
            , ( SaintVincentAndTheGrenadines	          , CountryName "Saint Vincent and the Grenadines"                  "Saint Vincent and the Grenadines"                     )
            , ( Samoa                                     , CountryName "Samoa"                                             "Independen State of Samoa"                            )
            , ( SanMarino                                 , CountryName "San Marino"                                        "Republic of San Marino"                               )
            , ( SaoTomeAndPrincipe                        , CountryName "Sao Tome and Principe"                             "Democratic Republic of Sao Tome and Principe"         )
            , ( SaudiArabia                               , CountryName "Saudi Arabia"                                      "Kingdom of Saudi Arabia"                              )
            , ( Senegal                                   , CountryName "Senegal"                                           "Republic of Senegal"                                  )
            , ( Serbia                                    , CountryName "Serbia"                                            "Republic of Serbia"                                   )
            , ( Seychelles                                , CountryName "Seychelles"                                        "Republic of Seychelles"                               )
            , ( SierraLeone                               , CountryName "Sierra Leone"                                      "Republic of Sierra Leone"                             )
            , ( Singapore                                 , CountryName "Singapore"                                         "Republic of Singapore"                                )
            , ( Slovakia                                  , CountryName "Slovakia"                                          "Slovak Republic"                                      )
            , ( Slovenia                                  , CountryName "Slovenia"                                          "Republic of Slovenia"                                 )
            , ( SolomonIslands                            , CountryName "Solomon Islands"                                   "Solomon Islands"                                      )
            , ( Somalia                                   , CountryName "Somalia"                                           "Somali Republic"                                      )
            , ( SouthAfrica                               , CountryName "South Africa"                                      "Republic of South Africa"                             )
            , ( SouthGeorgiaAndtheSouthSandwichIslands    , CountryName "South Georgia and the South Sandwich Islands"      "South Georgia And the South Sandwich Islands"         )
            , ( Spain                                     , CountryName "Spain"                                             "Kingdom of Spain"                                     )
            , ( SriLanka                                  , CountryName "Sri Lanka"                                         "Democratic Socialist Republic of Sri Lanka"           )
            , ( Sudan                                     , CountryName "Sudan"                                             "Republic of Sudan"                                    )
            , ( Suriname                                  , CountryName "Suriname"                                          "Republic of Suriname"                                 )
            , ( SvalbardAndJanMayen                       , CountryName "Svalbard And Jan Mayen"                            "Svalbard And Jan Mayen"                               )
            , ( Swaziland                                 , CountryName "Swaziland"                                         "Kingdom of Swaziland"                                 )
            , ( Sweden                                    , CountryName "Sweden"                                            "Kingdom of Sweden"                                    )
            , ( Switzerland                               , CountryName "Switzerland"                                       "Swiss Confederation"                                  )
            , ( Syria              	                      , CountryName "Syrian Arab Republic"                              "Syrian Arab Republic"                                 )
            , ( Taiwan                   	              , CountryName "Taiwan"                                            "Province of China, Taiwan"                            )
            , ( Tajikistan                                , CountryName "Tajikistan"                                        "Republic of Tajikistan"                               )
            , ( Tanzania                 	              , CountryName "Tanzania"                                          "United Republic of Tanzania"                          )
            , ( Thailand                                  , CountryName "Thailand"                                          "Kingdom of Thailand"                                  )
            , ( TimorLeste	                              , CountryName "Timor-Leste"                                       "Democratic Republic of Timor-Leste"                   )
            , ( Togo                                      , CountryName "Togo"                                              "Togolese Republic"                                    )
            , ( Tokelau                                   , CountryName "Tokelau"                                           "Tokelau"                                              )
            , ( Tonga                                     , CountryName "Tonga"                                             "Tonga"                                                )
            , ( TrinidadAndTobago                         , CountryName "Trinidad And Tobago"                               "Republic of Trinidad And Tobago"                      )
            , ( Tunisia                                   , CountryName "Tunisia"                                           "Republic of Tunisia"                                  )
            , ( Turkey                                    , CountryName "Turkey"                                            "Republic of Turkey"                                   )
            , ( Turkmenistan                              , CountryName "Turkmenistan"                                      "Turkmenistan"                                         )
            , ( TurksAndCaicosIslands                     , CountryName "Turks And Caicos Islands"                          "Turks And Caicos Islands"                             )
            , ( Tuvalu                                    , CountryName "Tuvalu"                                            "Tuvalu"                                               )
            , ( Uganda                                    , CountryName "Uganda"                                            "Republic of Uganda"                                   )
            , ( Ukraine                                   , CountryName "Ukraine"                                           "Ukraine"                                              )
            , ( UnitedArabEmirates                        , CountryName "United Arab Emirates"                              "United Arab Emirates"                                 )
            , ( UnitedKingdom                             , CountryName "United Kingdom"                                    "United Kingdom of Great Britain and Norther Ireland"  )
            , ( UnitedStates                              , CountryName "United States"                                     "United States of America"                             )
            , ( UnitedStatesMinorOutlyingIslands          , CountryName "United States Minor Outlying Islands"              "United States Minor Outlying Islands"                 )
            , ( Uruguay                                   , CountryName "Uruguay"                                           "Eastern Republic of Uruguay"                          )
            , ( Uzbekistan                                , CountryName "Uzbekistan"                                        "Republic of Uzbekistan"                               )
            , ( Vanuatu                                   , CountryName "Vanuatu"                                           "Republic of Vanuatu"                                  )
            , ( Venezuela                        	      , CountryName "Bolivia"                                           "Bolivarian Republic of Venezuela"                     )
            , ( VietNam                                   , CountryName "Vietnam"                                           "Socialist Republic of Viet Nam"                       )
            , ( BritishVirginIslands	                  , CountryName "British Virgin Islands"                            "British Virgin Islands"                               )
            , ( USVirginIslands	                          , CountryName "U.S. Virgin Islands"                               "U.S. Virgin Islands"                                  )
            , ( WallisAndFutuna                           , CountryName "Wallis And Futuna"                                 "Wallis And Futuna"                                    )
            , ( WesternSahara                             , CountryName "Western Sahara"                                    "Western Sahara"                                       )
            , ( Yemen                                     , CountryName "Yemen"                                             "Republic of Yemen"                                    )
            , ( Zambia                                    , CountryName "Zambia"                                            "Republic of Zambia"                                   )
            , ( Zimbabwe                                  , CountryName "Zimbabwe"                                          "Republic of Zimbabwe"                                 )
            ]