unicode-tricks-0.14.1.0: Functions to work with unicode blocks more convenient.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Emoji.Flag

Description

A module that defines the flag emoji. There are basically three types of flags: flags for nations, flags for subnations (like England, Scotland and Wales); and ExtraFlags that contain a list of flags used for occassions and political purposes.

Synopsis

Flag emoji

data Flag Source #

A data type that stores a (country) flag by the two characters of the ISO 3166 Alpa-2 standard. The data constructor is hidden to prevent making flags with a combination of characters that is invalid. Besides the countries defined in the ISO-3166 Alpha-2 standard, only the Antarctica (AQ), the European Union (EU) and the United Nations (UN) have a flag. Deprecated territories like the Soviet Union (SU) and Yugoslavia (YU) have no corresponding flag.

Instances

Instances details
Arbitrary Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

arbitrary :: Gen Flag #

shrink :: Flag -> [Flag] #

Data Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Flag -> c Flag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Flag #

toConstr :: Flag -> Constr #

dataTypeOf :: Flag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Flag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Flag) #

gmapT :: (forall b. Data b => b -> b) -> Flag -> Flag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Flag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Flag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Flag -> m Flag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag #

Bounded Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Enum Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

succ :: Flag -> Flag #

pred :: Flag -> Flag #

toEnum :: Int -> Flag #

fromEnum :: Flag -> Int #

enumFrom :: Flag -> [Flag] #

enumFromThen :: Flag -> Flag -> [Flag] #

enumFromTo :: Flag -> Flag -> [Flag] #

enumFromThenTo :: Flag -> Flag -> Flag -> [Flag] #

Generic Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Associated Types

type Rep Flag :: Type -> Type #

Methods

from :: Flag -> Rep Flag x #

to :: Rep Flag x -> Flag #

Read Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Show Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

NFData Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

rnf :: Flag -> () #

Eq Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

(==) :: Flag -> Flag -> Bool #

(/=) :: Flag -> Flag -> Bool #

Ord Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

(>=) :: Flag -> Flag -> Bool #

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Hashable Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

hashWithSalt :: Int -> Flag -> Int #

hash :: Flag -> Int #

UnicodeText Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

type Rep Flag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

type Rep Flag = D1 ('MetaData "Flag" "Data.Char.Emoji.Flag" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Flag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)))

flag Source #

Arguments

:: Char

The first character of the ISO 3166 Alpha-2 standard.

-> Char

The second character of the ISO 3166 Alpha-2 standard.

-> Maybe Flag

A Flag object wrapped in a Just data constructor, given such flag exists; Nothing otherwise.

Convert the given two characters that represent a flag according to the ISO 3166 Alpha-2 standard to a Flag wrapped in a Just data constructor, if that flag exists; Nothing otherwise. One can pass characters in upper case (A-Z) and lower case (a-z). The flag will hold the upper case variant. The Emoji have flags for the countries defined by the ISO 3166 Alpha-2 standard without deprecated regions like the Soviet Union (SU) and Yugoslavia (YU). Furthermore there are Emoji for the flags of Antarctica (AQ), the European Union (EU) and the United Nations (UN).

flag' Source #

Arguments

:: Char

The first character of the ISO 3166 Alpha-2 standard.

-> Char

The second character of the ISO 3166 Alpha-2 standard.

-> Flag

The equivalent Flag object.

Convert the given two characters that represent a flag according to the ISO 3166 Alpha-2 standard to a Flag. If the flag does not exists, then the result is unspecified. One can pass characters in upper case (A-Z) and lower case (a-z). The flag will hold the upper case variant. The Emoji have flags for the countries defined by the ISO 3166 Alpha-2 standard without deprecated regions like the Soviet Union (SU) and Yugoslavia (YU). Furthermore there are Emoji for the flags of Antarctica (AQ), the European Union (EU) and the United Nations (UN).

flagChars Source #

Arguments

:: Flag

The given Flag to convert to a 2-tuple of Characters.

-> (Char, Char)

A 2-tuple that contains upper case Characters for the given Flag.

Obtain the two-characters that specify the given Flag. These two characters are always upper case (A-Z).

iso3166Alpha2ToFlag Source #

Arguments

:: Char

The first Character of the ISO3166 Alpha-2 code.

-> Char

The second Character of the ISO3166 Alpha-2 code.

-> Maybe Text

A Text object that consists of two characters, where the two characters form a flag emoji wrapped in a Just, if the given flag exists; Nothing otherwise.

Convert the given two Characters of the ISO3166-1 Alpha-2 standard to an Emoji that renders the flag of the corresponding country or terroitory wrapped in a Just data constructor. Deprecated regions, such as SU (Soviet Union) and YU (Yugoslavia) have no flag. The European Union (EU), Antarctica (AQ) and United Nations (UN) are included as marcoregion flags. If the flag does not exists, Nothing is returned.

iso3166Alpha2ToFlag' Source #

Arguments

:: Char

The first Character of the ISO3166 Alpha-2 code.

-> Char

The second Character of the ISO3166 Alpha-2 code.

-> Text

A Text object that consists of two characters, where the two characters form a flag emoji, if the given flag exists.

Convert the given two Characters of the ISO3166-1 Alpha-2 standard to an Emoji that renders the flag of the corresponding country or terroitory. Deprecated regions, such as SU (Soviet Union) and YU (Yugoslavia) have no flag. The European Union (EU), Antarctica (AQ) and United Nations (UN) are included as marcoregion flags. This function does not check if the two characters map to a valid flag token.

validFlagEmoji Source #

Arguments

:: Char

The first Character of the ISO3166 Alpha-2 code.

-> Char

The second Character of the ISO3166 Alpha-2 code.

-> Bool

True if a flag emoji exists for the given characters; False otherwise.

Check if for the given two Characters, a flag emoji exists. The two character combinations for which a flag exist are defined in the ISO3166-1 Alpha-2 standard where deprecated reagions, such as SU and YU have no flag, and the European Union (EU), Antarctica (AQ), and the United Nations (UN) have a flag. The characters can be upper case (A-Z) or lower case (a-z).

Subregional flag emoji

data SubFlag Source #

A data type to store a subregion flag. This is specified by the parent flag, and three characters of the subregion. At the moment, the only three subregional flags are England (eng), Scotland (sct) and Wales (wls), all beloning under the United Kingdom flag (GB). The data constructor is made private to prevent making non-existing subflags.

Instances

Instances details
Arbitrary SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Data SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SubFlag -> c SubFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SubFlag #

toConstr :: SubFlag -> Constr #

dataTypeOf :: SubFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SubFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SubFlag) #

gmapT :: (forall b. Data b => b -> b) -> SubFlag -> SubFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SubFlag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SubFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> SubFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SubFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SubFlag -> m SubFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SubFlag -> m SubFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SubFlag -> m SubFlag #

Bounded SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Enum SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Generic SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Associated Types

type Rep SubFlag :: Type -> Type #

Methods

from :: SubFlag -> Rep SubFlag x #

to :: Rep SubFlag x -> SubFlag #

Read SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Show SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

NFData SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

rnf :: SubFlag -> () #

Eq SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

(==) :: SubFlag -> SubFlag -> Bool #

(/=) :: SubFlag -> SubFlag -> Bool #

Ord SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Hashable SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

hashWithSalt :: Int -> SubFlag -> Int #

hash :: SubFlag -> Int #

UnicodeText SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

type Rep SubFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

data ExtraFlag Source #

A data type to represent additional non-regional flags defined by the Unicode standard.

Constructors

ChequeredFlag

A flag with black and white square like in a checkerboard pattern. These are often used to signal the start or end of a car race. This is rendered as 🏁.

TriangularFlagOnPost

A triangular flag that is often used for golf. This is rendered as 🚩.

CrossedFlags

This emoji depicts two Japanese flags crossed at the base. Older versions of Samsung use two South Korean flags. This is rendered as 🎌.

BlackFlag

A waving black flag. This is rendered as 🏴.

WavingWhiteFlag

A waving white flag. This is often used as a sign of surrender. This is rendered as 🏳️.

RainbowFlag

A flag with six colors of the rainbow that usually include red, orange, yellow, green, blue and purple. This is rendered as 🏳️‍🌈.

TransgenderFlag

A flag with horizontal pale blue and pale pink stripes and a single white stripe in the middle. This is used as a transgender pride flag. This is rendered as 🏳️‍⚧️.

PirateFlag

A skull and crossbones displayed on a black flag. On pirate ships this is known as the Jolly Roger. This is rendered as 🏴‍☠️.

Instances

Instances details
Arbitrary ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Data ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExtraFlag -> c ExtraFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExtraFlag #

toConstr :: ExtraFlag -> Constr #

dataTypeOf :: ExtraFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExtraFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExtraFlag) #

gmapT :: (forall b. Data b => b -> b) -> ExtraFlag -> ExtraFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExtraFlag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExtraFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExtraFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExtraFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExtraFlag -> m ExtraFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExtraFlag -> m ExtraFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExtraFlag -> m ExtraFlag #

Bounded ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Enum ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Generic ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Associated Types

type Rep ExtraFlag :: Type -> Type #

Read ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Show ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

NFData ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Methods

rnf :: ExtraFlag -> () #

Eq ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Ord ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

Hashable ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

UnicodeText ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

type Rep ExtraFlag Source # 
Instance details

Defined in Data.Char.Emoji.Flag

type Rep ExtraFlag = D1 ('MetaData "ExtraFlag" "Data.Char.Emoji.Flag" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (((C1 ('MetaCons "ChequeredFlag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TriangularFlagOnPost" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CrossedFlags" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlackFlag" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WavingWhiteFlag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RainbowFlag" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TransgenderFlag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PirateFlag" 'PrefixI 'False) (U1 :: Type -> Type))))

Pattern symbols for Flags

pattern AC :: Flag Source #

The Flag pattern used for Ascension Island denoted with AC.

pattern AD :: Flag Source #

The Flag pattern used for Andorra denoted with AD.

pattern AE :: Flag Source #

The Flag pattern used for the United Arab Emirates denoted with AE.

pattern AF :: Flag Source #

The Flag pattern used for Afghanistan denoted with AF.

pattern AG :: Flag Source #

The Flag pattern used for Antigua & Barbuda denoted with AG.

pattern AI :: Flag Source #

The Flag pattern used for Anguilla denoted with AI.

pattern AL :: Flag Source #

The Flag pattern used for Albania denoted with AL.

pattern AM :: Flag Source #

The Flag pattern used for Armenia denoted with AM.

pattern AO :: Flag Source #

The Flag pattern used for Angola denoted with AO.

pattern AQ :: Flag Source #

The Flag pattern used for Antarctica denoted with AQ.

pattern AR :: Flag Source #

The Flag pattern used for Argentina denoted with AR.

pattern AS :: Flag Source #

The Flag pattern used for American Samoa denoted with AS.

pattern AT :: Flag Source #

The Flag pattern used for Austria denoted with AT.

pattern AU :: Flag Source #

The Flag pattern used for Australia denoted with AU.

pattern AW :: Flag Source #

The Flag pattern used for Aruba denoted with AW.

pattern AX :: Flag Source #

The Flag pattern used for the Åland Islands denoted with AX.

pattern AZ :: Flag Source #

The Flag pattern used for Azerbaijan denoted with AZ.

pattern BA :: Flag Source #

The Flag pattern used for Bosnia & Herzegovina denoted with BA.

pattern BB :: Flag Source #

The Flag pattern used for Barbados denoted with BB.

pattern BD :: Flag Source #

The Flag pattern used for Bangladesh denoted with BD.

pattern BE :: Flag Source #

The Flag pattern used for Belgium denoted with BE.

pattern BF :: Flag Source #

The Flag pattern used for Burkina Faso denoted with BF.

pattern BG :: Flag Source #

The Flag pattern used for Bulgaria denoted with BG.

pattern BH :: Flag Source #

The Flag pattern used for Bahrain denoted with BH.

pattern BI :: Flag Source #

The Flag pattern used for Burundi denoted with BI.

pattern BJ :: Flag Source #

The Flag pattern used for Benin denoted with BJ.

pattern BL :: Flag Source #

The Flag pattern used for St. Barthélemy denoted with BL.

pattern BM :: Flag Source #

The Flag pattern used for Bermuda denoted with BM.

pattern BN :: Flag Source #

The Flag pattern used for Brunei denoted with BN.

pattern BO :: Flag Source #

The Flag pattern used for Bolivia denoted with BO.

pattern BQ :: Flag Source #

The Flag pattern used for the Caribbean Netherlands denoted with BQ.

pattern BR :: Flag Source #

The Flag pattern used for Brazil denoted with BR.

pattern BS :: Flag Source #

The Flag pattern used for the Bahamas denoted with BS.

pattern BT :: Flag Source #

The Flag pattern used for Bhutan denoted with BT.

pattern BV :: Flag Source #

The Flag pattern used for Bouvet Island denoted with BV.

pattern BW :: Flag Source #

The Flag pattern used for Botswana denoted with BW.

pattern BY :: Flag Source #

The Flag pattern used for Belarus denoted with BY.

pattern BZ :: Flag Source #

The Flag pattern used for Belize denoted with BZ.

pattern CA :: Flag Source #

The Flag pattern used for Canada denoted with CA.

pattern CC :: Flag Source #

The Flag pattern used for the Cocos (Keeling) Islands denoted with CC.

pattern CD :: Flag Source #

The Flag pattern used for Congo - Kinshasa denoted with CD.

pattern CF :: Flag Source #

The Flag pattern used for Central African Republic denoted with CF.

pattern CG :: Flag Source #

The Flag pattern used for Congo - Brazzaville denoted with CG.

pattern CH :: Flag Source #

The Flag pattern used for Switzerland denoted with CH.

pattern CI :: Flag Source #

The Flag pattern used for Côte d’Ivoire denoted with CI.

pattern CK :: Flag Source #

The Flag pattern used for the Cook Islands denoted with CK.

pattern CL :: Flag Source #

The Flag pattern used for Chile denoted with CL.

pattern CM :: Flag Source #

The Flag pattern used for Cameroon denoted with CM.

pattern CN :: Flag Source #

The Flag pattern used for China denoted with CN.

pattern CO :: Flag Source #

The Flag pattern used for Colombia denoted with CO.

pattern CP :: Flag Source #

The Flag pattern used for Clipperton Island denoted with CP.

pattern CR :: Flag Source #

The Flag pattern used for Costa Rica denoted with CR.

pattern CU :: Flag Source #

The Flag pattern used for Cuba denoted with CU.

pattern CV :: Flag Source #

The Flag pattern used for Cape Verde denoted with CV.

pattern CW :: Flag Source #

The Flag pattern used for Curaçao denoted with CW.

pattern CX :: Flag Source #

The Flag pattern used for Christmas Island denoted with CX.

pattern CY :: Flag Source #

The Flag pattern used for Cyprus denoted with CY.

pattern CZ :: Flag Source #

The Flag pattern used for Czechia denoted with CZ.

pattern DE :: Flag Source #

The Flag pattern used for Germany denoted with DE.

pattern DG :: Flag Source #

The Flag pattern used for Diego Garcia denoted with DG.

pattern DJ :: Flag Source #

The Flag pattern used for Djibouti denoted with DJ.

pattern DK :: Flag Source #

The Flag pattern used for Denmark denoted with DK.

pattern DM :: Flag Source #

The Flag pattern used for Dominica denoted with DM.

pattern DO :: Flag Source #

The Flag pattern used for Dominican Republic denoted with DO.

pattern DZ :: Flag Source #

The Flag pattern used for Algeria denoted with DZ.

pattern EA :: Flag Source #

The Flag pattern used for Ceuta & Melilla denoted with EA.

pattern EC :: Flag Source #

The Flag pattern used for Ecuador denoted with EC.

pattern EE :: Flag Source #

The Flag pattern used for Estonia denoted with EE.

pattern EG :: Flag Source #

The Flag pattern used for Egypt denoted with EG.

pattern EH :: Flag Source #

The Flag pattern used for Western Sahara denoted with EH.

pattern ER :: Flag Source #

The Flag pattern used for Eritrea denoted with ER.

pattern ES :: Flag Source #

The Flag pattern used for Spain denoted with ES.

pattern ET :: Flag Source #

The Flag pattern used for Ethiopia denoted with ET.

pattern EU :: Flag Source #

The Flag pattern used for the European Union denoted with EU.

pattern FI :: Flag Source #

The Flag pattern used for Finland denoted with FI.

pattern FJ :: Flag Source #

The Flag pattern used for Fiji denoted with FJ.

pattern FK :: Flag Source #

The Flag pattern used for the Falkland Islands denoted with FK.

pattern FM :: Flag Source #

The Flag pattern used for Micronesia denoted with FM.

pattern FO :: Flag Source #

The Flag pattern used for the Faroe Islands denoted with FO.

pattern FR :: Flag Source #

The Flag pattern used for France denoted with FR.

pattern GA :: Flag Source #

The Flag pattern used for Gabon denoted with GA.

pattern GB :: Flag Source #

The Flag pattern used for United Kingdom denoted with GB.

pattern GD :: Flag Source #

The Flag pattern used for Grenada denoted with GD.

pattern GE :: Flag Source #

The Flag pattern used for Georgia denoted with GE.

pattern GF :: Flag Source #

The Flag pattern used for French Guiana denoted with GF.

pattern GG :: Flag Source #

The Flag pattern used for Guernsey denoted with GG.

pattern GH :: Flag Source #

The Flag pattern used for Ghana denoted with GH.

pattern GI :: Flag Source #

The Flag pattern used for Gibraltar denoted with GI.

pattern GL :: Flag Source #

The Flag pattern used for Greenland denoted with GL.

pattern GM :: Flag Source #

The Flag pattern used for Gambia denoted with GM.

pattern GN :: Flag Source #

The Flag pattern used for Guinea denoted with GN.

pattern GP :: Flag Source #

The Flag pattern used for Guadeloupe denoted with GP.

pattern GQ :: Flag Source #

The Flag pattern used for Equatorial Guinea denoted with GQ.

pattern GR :: Flag Source #

The Flag pattern used for Greece denoted with GR.

pattern GS :: Flag Source #

The Flag pattern used for the South Georgia & South Sandwich Islands denoted with GS.

pattern GT :: Flag Source #

The Flag pattern used for Guatemala denoted with GT.

pattern GU :: Flag Source #

The Flag pattern used for Guam denoted with GU.

pattern GW :: Flag Source #

The Flag pattern used for Guinea-Bissau denoted with GW.

pattern GY :: Flag Source #

The Flag pattern used for Guyana denoted with GY.

pattern HK :: Flag Source #

The Flag pattern used for Hong Kong SAR China denoted with HK.

pattern HM :: Flag Source #

The Flag pattern used for the Heard & McDonald Islands denoted with HM.

pattern HN :: Flag Source #

The Flag pattern used for Honduras denoted with HN.

pattern HR :: Flag Source #

The Flag pattern used for Croatia denoted with HR.

pattern HT :: Flag Source #

The Flag pattern used for Haiti denoted with HT.

pattern HU :: Flag Source #

The Flag pattern used for Hungary denoted with HU.

pattern IC :: Flag Source #

The Flag pattern used for the Canary Islands denoted with IC.

pattern ID :: Flag Source #

The Flag pattern used for Indonesia denoted with ID.

pattern IE :: Flag Source #

The Flag pattern used for Ireland denoted with IE.

pattern IL :: Flag Source #

The Flag pattern used for Israel denoted with IL.

pattern IM :: Flag Source #

The Flag pattern used for Isle of Man denoted with IM.

pattern IN :: Flag Source #

The Flag pattern used for India denoted with IN.

pattern IO :: Flag Source #

The Flag pattern used for British Indian Ocean Territory denoted with IO.

pattern IQ :: Flag Source #

The Flag pattern used for Iraq denoted with IQ.

pattern IR :: Flag Source #

The Flag pattern used for Iran denoted with IR.

pattern IS :: Flag Source #

The Flag pattern used for Iceland denoted with IS.

pattern IT :: Flag Source #

The Flag pattern used for Italy denoted with IT.

pattern JE :: Flag Source #

The Flag pattern used for Jersey denoted with JE.

pattern JM :: Flag Source #

The Flag pattern used for Jamaica denoted with JM.

pattern JO :: Flag Source #

The Flag pattern used for Jordan denoted with JO.

pattern JP :: Flag Source #

The Flag pattern used for Japan denoted with JP.

pattern KE :: Flag Source #

The Flag pattern used for Kenya denoted with KE.

pattern KG :: Flag Source #

The Flag pattern used for Kyrgyzstan denoted with KG.

pattern KH :: Flag Source #

The Flag pattern used for Cambodia denoted with KH.

pattern KI :: Flag Source #

The Flag pattern used for Kiribati denoted with KI.

pattern KM :: Flag Source #

The Flag pattern used for the Comoros denoted with KM.

pattern KN :: Flag Source #

The Flag pattern used for St. Kitts & Nevis denoted with KN.

pattern KP :: Flag Source #

The Flag pattern used for North Korea denoted with KP.

pattern KR :: Flag Source #

The Flag pattern used for South Korea denoted with KR.

pattern KW :: Flag Source #

The Flag pattern used for Kuwait denoted with KW.

pattern KY :: Flag Source #

The Flag pattern used for the Cayman Islands denoted with KY.

pattern KZ :: Flag Source #

The Flag pattern used for Kazakhstan denoted with KZ.

pattern LA :: Flag Source #

The Flag pattern used for Laos denoted with LA.

pattern LB :: Flag Source #

The Flag pattern used for Lebanon denoted with LB.

pattern LC :: Flag Source #

The Flag pattern used for St. Lucia denoted with LC.

pattern LI :: Flag Source #

The Flag pattern used for Liechtenstein denoted with LI.

pattern LK :: Flag Source #

The Flag pattern used for Sri Lanka denoted with LK.

pattern LR :: Flag Source #

The Flag pattern used for Liberia denoted with LR.

pattern LS :: Flag Source #

The Flag pattern used for Lesotho denoted with LS.

pattern LT :: Flag Source #

The Flag pattern used for Lithuania denoted with LT.

pattern LU :: Flag Source #

The Flag pattern used for Luxembourg denoted with LU.

pattern LV :: Flag Source #

The Flag pattern used for Latvia denoted with LV.

pattern LY :: Flag Source #

The Flag pattern used for Libya denoted with LY.

pattern MA :: Flag Source #

The Flag pattern used for Morocco denoted with MA.

pattern MC :: Flag Source #

The Flag pattern used for Monaco denoted with MC.

pattern MD :: Flag Source #

The Flag pattern used for Moldova denoted with MD.

pattern ME :: Flag Source #

The Flag pattern used for Montenegro denoted with ME.

pattern MF :: Flag Source #

The Flag pattern used for St. Martin denoted with MF.

pattern MG :: Flag Source #

The Flag pattern used for Madagascar denoted with MG.

pattern MH :: Flag Source #

The Flag pattern used for the Marshall Islands denoted with MH.

pattern MK :: Flag Source #

The Flag pattern used for North Macedonia denoted with MK.

pattern ML :: Flag Source #

The Flag pattern used for Mali denoted with ML.

pattern MM :: Flag Source #

The Flag pattern used for Myanmar (Burma) denoted with MM.

pattern MN :: Flag Source #

The Flag pattern used for Mongolia denoted with MN.

pattern MO :: Flag Source #

The Flag pattern used for Macao SAR China denoted with MO.

pattern MP :: Flag Source #

The Flag pattern used for the Northern Mariana Islands denoted with MP.

pattern MQ :: Flag Source #

The Flag pattern used for Martinique denoted with MQ.

pattern MR :: Flag Source #

The Flag pattern used for Mauritania denoted with MR.

pattern MS :: Flag Source #

The Flag pattern used for Montserrat denoted with MS.

pattern MT :: Flag Source #

The Flag pattern used for Malta denoted with MT.

pattern MU :: Flag Source #

The Flag pattern used for Mauritius denoted with MU.

pattern MV :: Flag Source #

The Flag pattern used for the Maldives denoted with MV.

pattern MW :: Flag Source #

The Flag pattern used for Malawi denoted with MW.

pattern MX :: Flag Source #

The Flag pattern used for Mexico denoted with MX.

pattern MY :: Flag Source #

The Flag pattern used for Malaysia denoted with MY.

pattern MZ :: Flag Source #

The Flag pattern used for Mozambique denoted with MZ.

pattern NA :: Flag Source #

The Flag pattern used for Namibia denoted with NA.

pattern NC :: Flag Source #

The Flag pattern used for New Caledonia denoted with NC.

pattern NE :: Flag Source #

The Flag pattern used for Niger denoted with NE.

pattern NF :: Flag Source #

The Flag pattern used for Norfolk Island denoted with NF.

pattern NG :: Flag Source #

The Flag pattern used for Nigeria denoted with NG.

pattern NI :: Flag Source #

The Flag pattern used for Nicaragua denoted with NI.

pattern NL :: Flag Source #

The Flag pattern used for the Netherlands denoted with NL.

pattern NO :: Flag Source #

The Flag pattern used for Norway denoted with NO.

pattern NP :: Flag Source #

The Flag pattern used for Nepal denoted with NP.

pattern NR :: Flag Source #

The Flag pattern used for Nauru denoted with NR.

pattern NU :: Flag Source #

The Flag pattern used for Niue denoted with NU.

pattern NZ :: Flag Source #

The Flag pattern used for New Zealand denoted with NZ.

pattern OM :: Flag Source #

The Flag pattern used for Oman denoted with OM.

pattern PA :: Flag Source #

The Flag pattern used for Panama denoted with PA.

pattern PE :: Flag Source #

The Flag pattern used for Peru denoted with PE.

pattern PF :: Flag Source #

The Flag pattern used for French Polynesia denoted with PF.

pattern PG :: Flag Source #

The Flag pattern used for Papua New Guinea denoted with PG.

pattern PH :: Flag Source #

The Flag pattern used for the Philippines denoted with PH.

pattern PK :: Flag Source #

The Flag pattern used for Pakistan denoted with PK.

pattern PL :: Flag Source #

The Flag pattern used for Poland denoted with PL.

pattern PM :: Flag Source #

The Flag pattern used for St. Pierre & Miquelon denoted with PM.

pattern PN :: Flag Source #

The Flag pattern used for the Pitcairn Islands denoted with PN.

pattern PR :: Flag Source #

The Flag pattern used for Puerto Rico denoted with PR.

pattern PS :: Flag Source #

The Flag pattern used for the Palestinian Territories denoted with PS.

pattern PT :: Flag Source #

The Flag pattern used for Portugal denoted with PT.

pattern PW :: Flag Source #

The Flag pattern used for Palau denoted with PW.

pattern PY :: Flag Source #

The Flag pattern used for Paraguay denoted with PY.

pattern QA :: Flag Source #

The Flag pattern used for Qatar denoted with QA.

pattern RE :: Flag Source #

The Flag pattern used for Réunion denoted with RE.

pattern RO :: Flag Source #

The Flag pattern used for Romania denoted with RO.

pattern RS :: Flag Source #

The Flag pattern used for Serbia denoted with RS.

pattern RU :: Flag Source #

The Flag pattern used for Russia denoted with RU.

pattern RW :: Flag Source #

The Flag pattern used for Rwanda denoted with RW.

pattern SA :: Flag Source #

The Flag pattern used for Saudi Arabia denoted with SA.

pattern SB :: Flag Source #

The Flag pattern used for the Solomon Islands denoted with SB.

pattern SC :: Flag Source #

The Flag pattern used for Seychelles denoted with SC.

pattern SD :: Flag Source #

The Flag pattern used for Sudan denoted with SD.

pattern SE :: Flag Source #

The Flag pattern used for Sweden denoted with SE.

pattern SG :: Flag Source #

The Flag pattern used for Singapore denoted with SG.

pattern SH :: Flag Source #

The Flag pattern used for St. Helena denoted with SH.

pattern SI :: Flag Source #

The Flag pattern used for Slovenia denoted with SI.

pattern SJ :: Flag Source #

The Flag pattern used for Svalbard & Jan Mayen denoted with SJ.

pattern SK :: Flag Source #

The Flag pattern used for Slovakia denoted with SK.

pattern SL :: Flag Source #

The Flag pattern used for Sierra Leone denoted with SL.

pattern SM :: Flag Source #

The Flag pattern used for San Marino denoted with SM.

pattern SN :: Flag Source #

The Flag pattern used for Senegal denoted with SN.

pattern SO :: Flag Source #

The Flag pattern used for Somalia denoted with SO.

pattern SR :: Flag Source #

The Flag pattern used for Suriname denoted with SR.

pattern SS :: Flag Source #

The Flag pattern used for South Sudan denoted with SS.

pattern ST :: Flag Source #

The Flag pattern used for São Tomé & Príncipe denoted with ST.

pattern SV :: Flag Source #

The Flag pattern used for El Salvador denoted with SV.

pattern SX :: Flag Source #

The Flag pattern used for Sint Maarten denoted with SX.

pattern SY :: Flag Source #

The Flag pattern used for Syria denoted with SY.

pattern SZ :: Flag Source #

The Flag pattern used for Eswatini denoted with SZ.

pattern TA :: Flag Source #

The Flag pattern used for Tristan da Cunha denoted with TA.

pattern TC :: Flag Source #

The Flag pattern used for the Turks & Caicos Islands denoted with TC.

pattern TD :: Flag Source #

The Flag pattern used for Chad denoted with TD.

pattern TF :: Flag Source #

The Flag pattern used for the French Southern Territories denoted with TF.

pattern TG :: Flag Source #

The Flag pattern used for Togo denoted with TG.

pattern TH :: Flag Source #

The Flag pattern used for Thailand denoted with TH.

pattern TJ :: Flag Source #

The Flag pattern used for Tajikistan denoted with TJ.

pattern TK :: Flag Source #

The Flag pattern used for Tokelau denoted with TK.

pattern TL :: Flag Source #

The Flag pattern used for Timor-Leste denoted with TL.

pattern TM :: Flag Source #

The Flag pattern used for Turkmenistan denoted with TM.

pattern TN :: Flag Source #

The Flag pattern used for Tunisia denoted with TN.

pattern TO :: Flag Source #

The Flag pattern used for Tonga denoted with TO.

pattern TR :: Flag Source #

The Flag pattern used for Turkey denoted with TR.

pattern TT :: Flag Source #

The Flag pattern used for Trinidad & Tobago denoted with TT.

pattern TV :: Flag Source #

The Flag pattern used for Tuvalu denoted with TV.

pattern TW :: Flag Source #

The Flag pattern used for Taiwan denoted with TW.

pattern TZ :: Flag Source #

The Flag pattern used for Tanzania denoted with TZ.

pattern UA :: Flag Source #

The Flag pattern used for Ukraine denoted with UA.

pattern UG :: Flag Source #

The Flag pattern used for Uganda denoted with UG.

pattern UM :: Flag Source #

The Flag pattern used for the U.S. Outlying Islands denoted with UM.

pattern UN :: Flag Source #

The Flag pattern used for the United Nations denoted with UN.

pattern US :: Flag Source #

The Flag pattern used for the United States denoted with US.

pattern UY :: Flag Source #

The Flag pattern used for Uruguay denoted with UY.

pattern UZ :: Flag Source #

The Flag pattern used for Uzbekistan denoted with UZ.

pattern VA :: Flag Source #

The Flag pattern used for Vatican City denoted with VA.

pattern VC :: Flag Source #

The Flag pattern used for St. Vincent & Grenadines denoted with VC.

pattern VE :: Flag Source #

The Flag pattern used for Venezuela denoted with VE.

pattern VG :: Flag Source #

The Flag pattern used for the British Virgin Islands denoted with VG.

pattern VI :: Flag Source #

The Flag pattern used for the U.S. Virgin Islands denoted with VI.

pattern VN :: Flag Source #

The Flag pattern used for Vietnam denoted with VN.

pattern VU :: Flag Source #

The Flag pattern used for Vanuatu denoted with VU.

pattern WF :: Flag Source #

The Flag pattern used for Wallis & Futuna denoted with WF.

pattern WS :: Flag Source #

The Flag pattern used for Samoa denoted with WS.

pattern XK :: Flag Source #

The Flag pattern used for Kosovo denoted with XK.

pattern YE :: Flag Source #

The Flag pattern used for Yemen denoted with YE.

pattern YT :: Flag Source #

The Flag pattern used for Mayotte denoted with YT.

pattern ZA :: Flag Source #

The Flag pattern used for South Africa denoted with ZA.

pattern ZM :: Flag Source #

The Flag pattern used for Zambia denoted with ZM.

pattern ZW :: Flag Source #

The Flag pattern used for Zimbabwe denoted with ZW.

Pattern synonyms for SubFlags

pattern ENG :: SubFlag Source #

The SubFlag pattern used for England denoted with GB-ENG or ENG.

pattern SCT :: SubFlag Source #

The SubFlag pattern used for Scotland denoted with GB-SCT or SCT.

pattern WLS :: SubFlag Source #

The SubFlag pattern used for Wales denoted with GB-WLS or WLS.

pattern USAL :: SubFlag Source #

The SubFlag pattern used for Alabama denoted with US-AL or AL

pattern USAK :: SubFlag Source #

The SubFlag pattern used for Alaska denoted with US-AK or AK

pattern USAS :: SubFlag Source #

The SubFlag pattern used for American Samoa denoted with US-AS or AS

pattern USAZ :: SubFlag Source #

The SubFlag pattern used for Arizona denoted with US-AZ or AZ

pattern USAR :: SubFlag Source #

The SubFlag pattern used for Arkansas denoted with US-AR or AR

pattern USCA :: SubFlag Source #

The SubFlag pattern used for California denoted with US-CA or CA

pattern USCO :: SubFlag Source #

The SubFlag pattern used for Colorado denoted with US-CO or CO

pattern USCT :: SubFlag Source #

The SubFlag pattern used for Connecticut denoted with US-CT or CT

pattern USDE :: SubFlag Source #

The SubFlag pattern used for Delaware denoted with US-DE or DE

pattern USFL :: SubFlag Source #

The SubFlag pattern used for Florida denoted with US-FL or FL

pattern USGA :: SubFlag Source #

The SubFlag pattern used for Georgia denoted with US-GA or GA

pattern USGU :: SubFlag Source #

The SubFlag pattern used for Guam denoted with US-GU or GU

pattern USHI :: SubFlag Source #

The SubFlag pattern used for Hawaii denoted with US-HI or HI

pattern USID :: SubFlag Source #

The SubFlag pattern used for Idaho denoted with US-ID or ID

pattern USIL :: SubFlag Source #

The SubFlag pattern used for Illinois denoted with US-IL or IL

pattern USIN :: SubFlag Source #

The SubFlag pattern used for Indiana denoted with US-IN or IN

pattern USIA :: SubFlag Source #

The SubFlag pattern used for Iowa denoted with US-IA or IA

pattern USKS :: SubFlag Source #

The SubFlag pattern used for Kansas denoted with US-KS or KS

pattern USKY :: SubFlag Source #

The SubFlag pattern used for Kentucky denoted with US-KY or KY

pattern USLA :: SubFlag Source #

The SubFlag pattern used for Louisiana denoted with US-LA or LA

pattern USME :: SubFlag Source #

The SubFlag pattern used for Maine denoted with US-ME or ME

pattern USMD :: SubFlag Source #

The SubFlag pattern used for Maryland denoted with US-MD or MD

pattern USMA :: SubFlag Source #

The SubFlag pattern used for Massachusetts denoted with US-MA or MA

pattern USMI :: SubFlag Source #

The SubFlag pattern used for Michigan denoted with US-MI or MI

pattern USMN :: SubFlag Source #

The SubFlag pattern used for Minnesota denoted with US-MN or MN

pattern USMS :: SubFlag Source #

The SubFlag pattern used for Mississippi denoted with US-MS or MS

pattern USMO :: SubFlag Source #

The SubFlag pattern used for Missouri denoted with US-MO or MO

pattern USMT :: SubFlag Source #

The SubFlag pattern used for Montana denoted with US-MT or MT

pattern USNE :: SubFlag Source #

The SubFlag pattern used for Nebraska denoted with US-NE or NE

pattern USNV :: SubFlag Source #

The SubFlag pattern used for Nevada denoted with US-NV or NV

pattern USNH :: SubFlag Source #

The SubFlag pattern used for New Hampshire denoted with US-NH or NH

pattern USNJ :: SubFlag Source #

The SubFlag pattern used for New Jersey denoted with US-NJ or NJ

pattern USNM :: SubFlag Source #

The SubFlag pattern used for New Mexico denoted with US-NM or NM

pattern USNY :: SubFlag Source #

The SubFlag pattern used for New York denoted with US-NY or NY

pattern USNC :: SubFlag Source #

The SubFlag pattern used for North Carolina denoted with US-NC or NC

pattern USND :: SubFlag Source #

The SubFlag pattern used for North Dakota denoted with US-ND or ND

pattern USMP :: SubFlag Source #

The SubFlag pattern used for Northern Mariana Islands denoted with US-MP or MP

pattern USOH :: SubFlag Source #

The SubFlag pattern used for Ohio denoted with US-OH or OH

pattern USOK :: SubFlag Source #

The SubFlag pattern used for Oklahoma denoted with US-OK or OK

pattern USOR :: SubFlag Source #

The SubFlag pattern used for Oregon denoted with US-OR or OR

pattern USPA :: SubFlag Source #

The SubFlag pattern used for Pennsylvania denoted with US-PA or PA

pattern USPR :: SubFlag Source #

The SubFlag pattern used for Puerto Rico denoted with US-PR or PR

pattern USRI :: SubFlag Source #

The SubFlag pattern used for Rhode Island denoted with US-RI or RI

pattern USSC :: SubFlag Source #

The SubFlag pattern used for South Carolina denoted with US-SC or SC

pattern USSD :: SubFlag Source #

The SubFlag pattern used for South Dakota denoted with US-SD or SD

pattern USTN :: SubFlag Source #

The SubFlag pattern used for Tennessee denoted with US-TN or TN

pattern USUM :: SubFlag Source #

The SubFlag pattern used for U.S. Outlying Islands denoted with US-UM or UM

pattern USVI :: SubFlag Source #

The SubFlag pattern used for U.S. Virgin Islands denoted with US-VI or VI

pattern USUT :: SubFlag Source #

The SubFlag pattern used for Utah denoted with US-UT or UT

pattern USVT :: SubFlag Source #

The SubFlag pattern used for Vermont denoted with US-VT or VT

pattern USVA :: SubFlag Source #

The SubFlag pattern used for Virginia denoted with US-VA or VA

pattern USWA :: SubFlag Source #

The SubFlag pattern used for Washington denoted with US-WA or WA

pattern USDC :: SubFlag Source #

The SubFlag pattern used for Washington DC denoted with US-DC or DC

pattern USWV :: SubFlag Source #

The SubFlag pattern used for West Virginia denoted with US-WV or WV

pattern USWI :: SubFlag Source #

The SubFlag pattern used for Wisconsin denoted with US-WI or WI

pattern USWY :: SubFlag Source #

The SubFlag pattern used for Wyoming denoted with US-WY or WY