{-# OPTIONS_GHC -fwarn-incomplete-patterns #-} {-# OPTIONS_GHC -fwarn-missing-methods #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE ViewPatterns #-} module Facts.Geography.Countries ( Country (..) -- , ISOAlpha2Code (..) , ISOAlpha3Code (..) , ISONumericCode , UNFormalName , UNShortName , isoNumericCode , shortEnglishCountryName , formalEnglishCountryName , isoAlpha2Code_for_country , isoAlpha3Code_for_country , country_for_isoAlpha2Code , country_for_isoAlpha3Code , isoNumericCode_for_country , country_for_valid_isoNumericCode , country_for_isoNumericCode ) where import Data.Numerals.Decimal import Facts.Geography.Countries.Internal.Splices import Facts.Geography.Countries.Internal.Data import Test.QuickCheck import Test.QuickCheck.Gen instance Show Country where show = shortEnglishCountryName -- | Maps a 'Country' to its ISO-3166-1 2-character code. isoAlpha2Code_for_country :: Country -> ISOAlpha2Code -- | Maps a 'Country' to its ISO-3166-1 3-character code. isoAlpha3Code_for_country :: Country -> ISOAlpha3Code -- | Maps a 'Country' to its ISO-3166-1 numeric code. isoNumericCode_for_country :: Country -> ISONumericCode -- | Maps an ISO-3166-1 2-character code to a 'Country'. country_for_isoAlpha2Code :: ISOAlpha2Code -> Country -- | Maps an ISO-3166-1 3-character code to a 'Country'. country_for_isoAlpha3Code :: ISOAlpha3Code -> Country country_code_by_country = _country_code_by_country country_by_country_code = _country_by_country_code country_name_by_country = _country_name_by_country isoAlpha2Code_for_country = _isoAlpha2_for_country isoAlpha3Code_for_country = _isoAlpha3_for_country isoNumericCode_for_country = _isoNumeric_for_country country_for_isoAlpha2Code = _country_for_isoAlpha2 country_for_isoAlpha3Code = _country_for_isoAlpha3 -- | The ISO Numeric Code space is not fully packed. Many codes are \"reserved\" or otherwise -- unused. 'country_for_isoNumericCode' takes an 'ISONumericCode' and possibly returns a matching -- 'Country'. country_for_isoNumericCode :: ISONumericCode -> Maybe Country country_for_isoNumericCode = (fmap country_for_valid_isoNumericCode) . validate_isoNumericCode -- | 'country_for_valid_isoNumericCode' maps a valid 'ISONumericCode' to a 'Country'. Unfortunately, -- this is a partial function. Use 'country_for_isoNumericCode' instead, unless you can guarantee -- that the 'ISONumericCode' supplied to the query is valid. country_for_valid_isoNumericCode :: ISONumericCode -> Country country_for_valid_isoNumericCode = _country_for_isoNumeric -- | 'shortEnglishCountryName' maps a Country to an ISO-3166-1 \"short name\". By the international -- standard, these names are taken from the \"United Nations Terminology Bulletin Country Names\", -- and \"Country and Region Codes for Statistical Use\" of the UN Statistics Division. shortEnglishCountryName :: Country -> UNShortName shortEnglishCountryName = _shortEnglishCountryName -- | 'formalEnglishCountryName' maps a Country to an ISO-3166-1 \"formal name\". By the international -- standard, these names are taken from the \"United Nations Terminology Bulletin Country Names\", -- and \"Country and Region Codes for Statistical Use\" of the UN Statistics Division. formalEnglishCountryName :: Country -> UNFormalName formalEnglishCountryName = _formalEnglishCountryName instance Arbitrary Country where arbitrary = elements [Afghanistan .. Zimbabwe] newtype ValidCode = ValidCode ISOCountryCode deriving (Show) instance Arbitrary ValidCode where arbitrary = elements . fmap (ValidCode) $ valid_iso_country_codes prop_country_to_code_roundtrip :: Country -> Bool prop_country_to_code_roundtrip country = (country_by_country_code . country_code_by_country $ country) == country prop_code_to_country_roundtrip :: ValidCode -> Bool prop_code_to_country_roundtrip (ValidCode code) = (country_code_by_country . country_by_country_code $ code) == code