tztime-0.1.1.0: Safe timezone-aware handling of time.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Time.TZInfo

Synopsis

Documentation

data TZInfo Source #

A time zone.

There are two main ways of loading a TZInfo:

  1. Load it from the operating system's time zone database, using loadFromSystem, loadFromFile or getCurrentTZInfo.
  2. Load it from the embedded database, using fromIdentifier or fromLabel.

    This package depends on the tzdata package, which comes with an embedded IANA time zone database.

The embedded database has the benefit of being portable, that is, it works regardless of your operating system. The functions to read from the system database, on the other hand, aren't portable; loadFromSystem and getCurrentTZInfo are not likely to work on Windows.

However, you have to make sure you're always using the latest version of tzdata to get the latest updates. The operating system's time zone database is usually easier to keep up-to-date.

Constructors

TZInfo 

Fields

Instances

Instances details
Data TZInfo Source # 
Instance details

Defined in Data.Time.TZInfo

Methods

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

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

toConstr :: TZInfo -> Constr #

dataTypeOf :: TZInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TZInfo Source # 
Instance details

Defined in Data.Time.TZInfo

Associated Types

type Rep TZInfo :: Type -> Type #

Methods

from :: TZInfo -> Rep TZInfo x #

to :: Rep TZInfo x -> TZInfo #

Show TZInfo Source # 
Instance details

Defined in Data.Time.TZInfo

NFData TZInfo Source # 
Instance details

Defined in Data.Time.TZInfo

Methods

rnf :: TZInfo -> () #

Eq TZInfo Source # 
Instance details

Defined in Data.Time.TZInfo

Methods

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

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

HasField "tzTimeTZInfo" TZTime TZInfo Source #

Since: 0.1.1.0

Instance details

Defined in Data.Time.TZTime.Internal

Methods

getField :: TZTime -> TZInfo #

type Rep TZInfo Source # 
Instance details

Defined in Data.Time.TZInfo

type Rep TZInfo = D1 ('MetaData "TZInfo" "Data.Time.TZInfo" "tztime-0.1.1.0-AlwWFgZtNspHPa4GB9WvU4" 'False) (C1 ('MetaCons "TZInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "tziIdentifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TZIdentifier) :*: S1 ('MetaSel ('Just "tziRules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TZ)))

type TZIdentifier = Text Source #

A time zone's identifier, e.g. Europe/Paris.

utc :: TZInfo Source #

The UTC time zone.

System's time zone database

loadFromSystem :: TZIdentifier -> IO TZInfo Source #

Looks for the time zone file in the system time zone directory, which is /usr/share/zoneinfo, or if the TZDIR environment variable is set, then there.

Note, this is unlikely to work on non-posix systems (e.g., Windows). Use fromIdentifier, fromLabel or loadFromFile instead.

Throws an IOException if the identifier is not found.

loadFromFile :: TZIdentifier -> FilePath -> IO TZInfo Source #

Reads and parses a time zone information file (in tzfile(5) aka. Olson file format).

getCurrentTZInfo :: IO TZInfo Source #

Returns the local TZInfo based on the TZ and TZDIR environment variables.

See tzset(3) for details, but basically:

  • If TZ environment variable is unset, we use /etc/localtime.
  • If TZ is set, but empty, we use utc.
  • If TZ is set and not empty, we use loadFromSystem to read that file.

Embedded time zone database

fromIdentifier :: TZIdentifier -> Maybe TZInfo Source #

Look up a time zone in the tzdata's embedded database.

fromLabel :: TZLabel -> TZInfo Source #

Retrieves the time zone info for a "canonical" time zone from tzdata's embedded database.

TZLabel

TZLabel enumerates all the "canonical" time zones from the IANA database.

For example, the 2022a version of the IANA database defines Europe/London as a "canonical" time zone and Europe/Jersey, Europe/Guernsey and Europe/Isle_of_Man as links to Europe/London.

Zone	Europe/London	-0:01:15 -	LMT	1847 Dec  1  0:00s
			 ...
Link	Europe/London	Europe/Jersey
Link	Europe/London	Europe/Guernsey
Link	Europe/London	Europe/Isle_of_Man

Note that fromLabel only supports canonical time zone identifiers, whereas fromIdentifier supports all time zone identifiers.

data TZLabel #

Enumeration of time zone locations.

Constructors

Africa__Abidjan 
Africa__Accra 
Africa__Addis_Ababa 
Africa__Algiers 
Africa__Asmara 
Africa__Asmera 
Africa__Bamako 
Africa__Bangui 
Africa__Banjul 
Africa__Bissau 
Africa__Blantyre 
Africa__Brazzaville 
Africa__Bujumbura 
Africa__Cairo 
Africa__Casablanca 
Africa__Ceuta 
Africa__Conakry 
Africa__Dakar 
Africa__Dar_es_Salaam 
Africa__Djibouti 
Africa__Douala 
Africa__El_Aaiun 
Africa__Freetown 
Africa__Gaborone 
Africa__Harare 
Africa__Johannesburg 
Africa__Juba 
Africa__Kampala 
Africa__Khartoum 
Africa__Kigali 
Africa__Kinshasa 
Africa__Lagos 
Africa__Libreville 
Africa__Lome 
Africa__Luanda 
Africa__Lubumbashi 
Africa__Lusaka 
Africa__Malabo 
Africa__Maputo 
Africa__Maseru 
Africa__Mbabane 
Africa__Mogadishu 
Africa__Monrovia 
Africa__Nairobi 
Africa__Ndjamena 
Africa__Niamey 
Africa__Nouakchott 
Africa__Ouagadougou 
Africa__Porto_Novo 
Africa__Sao_Tome 
Africa__Timbuktu 
Africa__Tripoli 
Africa__Tunis 
Africa__Windhoek 
America__Adak 
America__Anchorage 
America__Anguilla 
America__Antigua 
America__Araguaina 
America__Argentina__Buenos_Aires 
America__Argentina__Catamarca 
America__Argentina__ComodRivadavia 
America__Argentina__Cordoba 
America__Argentina__Jujuy 
America__Argentina__La_Rioja 
America__Argentina__Mendoza 
America__Argentina__Rio_Gallegos 
America__Argentina__Salta 
America__Argentina__San_Juan 
America__Argentina__San_Luis 
America__Argentina__Tucuman 
America__Argentina__Ushuaia 
America__Aruba 
America__Asuncion 
America__Atikokan 
America__Atka 
America__Bahia 
America__Bahia_Banderas 
America__Barbados 
America__Belem 
America__Belize 
America__Blanc_Sablon 
America__Boa_Vista 
America__Bogota 
America__Boise 
America__Buenos_Aires 
America__Cambridge_Bay 
America__Campo_Grande 
America__Cancun 
America__Caracas 
America__Catamarca 
America__Cayenne 
America__Cayman 
America__Chicago 
America__Chihuahua 
America__Ciudad_Juarez 
America__Coral_Harbour 
America__Cordoba 
America__Costa_Rica 
America__Creston 
America__Cuiaba 
America__Curacao 
America__Danmarkshavn 
America__Dawson 
America__Dawson_Creek 
America__Denver 
America__Detroit 
America__Dominica 
America__Edmonton 
America__Eirunepe 
America__El_Salvador 
America__Ensenada 
America__Fort_Nelson 
America__Fort_Wayne 
America__Fortaleza 
America__Glace_Bay 
America__Godthab 
America__Goose_Bay 
America__Grand_Turk 
America__Grenada 
America__Guadeloupe 
America__Guatemala 
America__Guayaquil 
America__Guyana 
America__Halifax 
America__Havana 
America__Hermosillo 
America__Indiana__Indianapolis 
America__Indiana__Knox 
America__Indiana__Marengo 
America__Indiana__Petersburg 
America__Indiana__Tell_City 
America__Indiana__Vevay 
America__Indiana__Vincennes 
America__Indiana__Winamac 
America__Indianapolis 
America__Inuvik 
America__Iqaluit 
America__Jamaica 
America__Jujuy 
America__Juneau 
America__Kentucky__Louisville 
America__Kentucky__Monticello 
America__Knox_IN 
America__Kralendijk 
America__La_Paz 
America__Lima 
America__Los_Angeles 
America__Louisville 
America__Lower_Princes 
America__Maceio 
America__Managua 
America__Manaus 
America__Marigot 
America__Martinique 
America__Matamoros 
America__Mazatlan 
America__Mendoza 
America__Menominee 
America__Merida 
America__Metlakatla 
America__Mexico_City 
America__Miquelon 
America__Moncton 
America__Monterrey 
America__Montevideo 
America__Montreal 
America__Montserrat 
America__Nassau 
America__New_York 
America__Nipigon 
America__Nome 
America__Noronha 
America__North_Dakota__Beulah 
America__North_Dakota__Center 
America__North_Dakota__New_Salem 
America__Nuuk 
America__Ojinaga 
America__Panama 
America__Pangnirtung 
America__Paramaribo 
America__Phoenix 
America__Port_au_Prince 
America__Port_of_Spain 
America__Porto_Acre 
America__Porto_Velho 
America__Puerto_Rico 
America__Punta_Arenas 
America__Rainy_River 
America__Rankin_Inlet 
America__Recife 
America__Regina 
America__Resolute 
America__Rio_Branco 
America__Rosario 
America__Santa_Isabel 
America__Santarem 
America__Santiago 
America__Santo_Domingo 
America__Sao_Paulo 
America__Scoresbysund 
America__Shiprock 
America__Sitka 
America__St_Barthelemy 
America__St_Johns 
America__St_Kitts 
America__St_Lucia 
America__St_Thomas 
America__St_Vincent 
America__Swift_Current 
America__Tegucigalpa 
America__Thule 
America__Thunder_Bay 
America__Tijuana 
America__Toronto 
America__Tortola 
America__Vancouver 
America__Virgin 
America__Whitehorse 
America__Winnipeg 
America__Yakutat 
America__Yellowknife 
Antarctica__Casey 
Antarctica__Davis 
Antarctica__DumontDUrville 
Antarctica__Macquarie 
Antarctica__Mawson 
Antarctica__McMurdo 
Antarctica__Palmer 
Antarctica__Rothera 
Antarctica__South_Pole 
Antarctica__Syowa 
Antarctica__Troll 
Antarctica__Vostok 
Arctic__Longyearbyen 
Asia__Aden 
Asia__Almaty 
Asia__Amman 
Asia__Anadyr 
Asia__Aqtau 
Asia__Aqtobe 
Asia__Ashgabat 
Asia__Ashkhabad 
Asia__Atyrau 
Asia__Baghdad 
Asia__Bahrain 
Asia__Baku 
Asia__Bangkok 
Asia__Barnaul 
Asia__Beirut 
Asia__Bishkek 
Asia__Brunei 
Asia__Calcutta 
Asia__Chita 
Asia__Choibalsan 
Asia__Chongqing 
Asia__Chungking 
Asia__Colombo 
Asia__Dacca 
Asia__Damascus 
Asia__Dhaka 
Asia__Dili 
Asia__Dubai 
Asia__Dushanbe 
Asia__Famagusta 
Asia__Gaza 
Asia__Harbin 
Asia__Hebron 
Asia__Ho_Chi_Minh 
Asia__Hong_Kong 
Asia__Hovd 
Asia__Irkutsk 
Asia__Istanbul 
Asia__Jakarta 
Asia__Jayapura 
Asia__Jerusalem 
Asia__Kabul 
Asia__Kamchatka 
Asia__Karachi 
Asia__Kashgar 
Asia__Kathmandu 
Asia__Katmandu 
Asia__Khandyga 
Asia__Kolkata 
Asia__Krasnoyarsk 
Asia__Kuala_Lumpur 
Asia__Kuching 
Asia__Kuwait 
Asia__Macao 
Asia__Macau 
Asia__Magadan 
Asia__Makassar 
Asia__Manila 
Asia__Muscat 
Asia__Nicosia 
Asia__Novokuznetsk 
Asia__Novosibirsk 
Asia__Omsk 
Asia__Oral 
Asia__Phnom_Penh 
Asia__Pontianak 
Asia__Pyongyang 
Asia__Qatar 
Asia__Qostanay 
Asia__Qyzylorda 
Asia__Rangoon 
Asia__Riyadh 
Asia__Saigon 
Asia__Sakhalin 
Asia__Samarkand 
Asia__Seoul 
Asia__Shanghai 
Asia__Singapore 
Asia__Srednekolymsk 
Asia__Taipei 
Asia__Tashkent 
Asia__Tbilisi 
Asia__Tehran 
Asia__Tel_Aviv 
Asia__Thimbu 
Asia__Thimphu 
Asia__Tokyo 
Asia__Tomsk 
Asia__Ujung_Pandang 
Asia__Ulaanbaatar 
Asia__Ulan_Bator 
Asia__Urumqi 
Asia__Ust_Nera 
Asia__Vientiane 
Asia__Vladivostok 
Asia__Yakutsk 
Asia__Yangon 
Asia__Yekaterinburg 
Asia__Yerevan 
Atlantic__Azores 
Atlantic__Bermuda 
Atlantic__Canary 
Atlantic__Cape_Verde 
Atlantic__Faeroe 
Atlantic__Faroe 
Atlantic__Jan_Mayen 
Atlantic__Madeira 
Atlantic__Reykjavik 
Atlantic__South_Georgia 
Atlantic__St_Helena 
Atlantic__Stanley 
Australia__ACT 
Australia__Adelaide 
Australia__Brisbane 
Australia__Broken_Hill 
Australia__Canberra 
Australia__Currie 
Australia__Darwin 
Australia__Eucla 
Australia__Hobart 
Australia__LHI 
Australia__Lindeman 
Australia__Lord_Howe 
Australia__Melbourne 
Australia__NSW 
Australia__North 
Australia__Perth 
Australia__Queensland 
Australia__South 
Australia__Sydney 
Australia__Tasmania 
Australia__Victoria 
Australia__West 
Australia__Yancowinna 
Brazil__Acre 
Brazil__DeNoronha 
Brazil__East 
Brazil__West 
CET 
CST6CDT 
Canada__Atlantic 
Canada__Central 
Canada__Eastern 
Canada__Mountain 
Canada__Newfoundland 
Canada__Pacific 
Canada__Saskatchewan 
Canada__Yukon 
Chile__Continental 
Chile__EasterIsland 
Cuba 
EET 
EST 
EST5EDT 
Egypt 
Eire 
Etc__GMT 
Etc__GMT'0 
Etc__GMT'1 
Etc__GMT'10 
Etc__GMT'11 
Etc__GMT'12 
Etc__GMT'2 
Etc__GMT'3 
Etc__GMT'4 
Etc__GMT'5 
Etc__GMT'6 
Etc__GMT'7 
Etc__GMT'8 
Etc__GMT'9 
Etc__GMT_0 
Etc__GMT_1 
Etc__GMT_10 
Etc__GMT_11 
Etc__GMT_12 
Etc__GMT_13 
Etc__GMT_14 
Etc__GMT_2 
Etc__GMT_3 
Etc__GMT_4 
Etc__GMT_5 
Etc__GMT_6 
Etc__GMT_7 
Etc__GMT_8 
Etc__GMT_9 
Etc__GMT0 
Etc__Greenwich 
Etc__UCT 
Etc__UTC 
Etc__Universal 
Etc__Zulu 
Europe__Amsterdam 
Europe__Andorra 
Europe__Astrakhan 
Europe__Athens 
Europe__Belfast 
Europe__Belgrade 
Europe__Berlin 
Europe__Bratislava 
Europe__Brussels 
Europe__Bucharest 
Europe__Budapest 
Europe__Busingen 
Europe__Chisinau 
Europe__Copenhagen 
Europe__Dublin 
Europe__Gibraltar 
Europe__Guernsey 
Europe__Helsinki 
Europe__Isle_of_Man 
Europe__Istanbul 
Europe__Jersey 
Europe__Kaliningrad 
Europe__Kiev 
Europe__Kirov 
Europe__Kyiv 
Europe__Lisbon 
Europe__Ljubljana 
Europe__London 
Europe__Luxembourg 
Europe__Madrid 
Europe__Malta 
Europe__Mariehamn 
Europe__Minsk 
Europe__Monaco 
Europe__Moscow 
Europe__Nicosia 
Europe__Oslo 
Europe__Paris 
Europe__Podgorica 
Europe__Prague 
Europe__Riga 
Europe__Rome 
Europe__Samara 
Europe__San_Marino 
Europe__Sarajevo 
Europe__Saratov 
Europe__Simferopol 
Europe__Skopje 
Europe__Sofia 
Europe__Stockholm 
Europe__Tallinn 
Europe__Tirane 
Europe__Tiraspol 
Europe__Ulyanovsk 
Europe__Uzhgorod 
Europe__Vaduz 
Europe__Vatican 
Europe__Vienna 
Europe__Vilnius 
Europe__Volgograd 
Europe__Warsaw 
Europe__Zagreb 
Europe__Zaporozhye 
Europe__Zurich 
Factory 
GB 
GB_Eire 
GMT 
GMT'0 
GMT_0 
GMT0 
Greenwich 
HST 
Hongkong 
Iceland 
Indian__Antananarivo 
Indian__Chagos 
Indian__Christmas 
Indian__Cocos 
Indian__Comoro 
Indian__Kerguelen 
Indian__Mahe 
Indian__Maldives 
Indian__Mauritius 
Indian__Mayotte 
Indian__Reunion 
Iran 
Israel 
Jamaica 
Japan 
Kwajalein 
Libya 
MET 
MST 
MST7MDT 
Mexico__BajaNorte 
Mexico__BajaSur 
Mexico__General 
NZ 
NZ_CHAT 
Navajo 
PRC 
PST8PDT 
Pacific__Apia 
Pacific__Auckland 
Pacific__Bougainville 
Pacific__Chatham 
Pacific__Chuuk 
Pacific__Easter 
Pacific__Efate 
Pacific__Enderbury 
Pacific__Fakaofo 
Pacific__Fiji 
Pacific__Funafuti 
Pacific__Galapagos 
Pacific__Gambier 
Pacific__Guadalcanal 
Pacific__Guam 
Pacific__Honolulu 
Pacific__Johnston 
Pacific__Kanton 
Pacific__Kiritimati 
Pacific__Kosrae 
Pacific__Kwajalein 
Pacific__Majuro 
Pacific__Marquesas 
Pacific__Midway 
Pacific__Nauru 
Pacific__Niue 
Pacific__Norfolk 
Pacific__Noumea 
Pacific__Pago_Pago 
Pacific__Palau 
Pacific__Pitcairn 
Pacific__Pohnpei 
Pacific__Ponape 
Pacific__Port_Moresby 
Pacific__Rarotonga 
Pacific__Saipan 
Pacific__Samoa 
Pacific__Tahiti 
Pacific__Tarawa 
Pacific__Tongatapu 
Pacific__Truk 
Pacific__Wake 
Pacific__Wallis 
Pacific__Yap 
Poland 
Portugal 
ROC 
ROK 
Singapore 
Turkey 
UCT 
US__Alaska 
US__Aleutian 
US__Arizona 
US__Central 
US__East_Indiana 
US__Eastern 
US__Hawaii 
US__Indiana_Starke 
US__Michigan 
US__Mountain 
US__Pacific 
US__Samoa 
UTC 
Universal 
W_SU 
WET 
Zulu 

Instances

Instances details
Data TZLabel 
Instance details

Defined in Data.Time.Zones.DB

Methods

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

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

toConstr :: TZLabel -> Constr #

dataTypeOf :: TZLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded TZLabel 
Instance details

Defined in Data.Time.Zones.DB

Enum TZLabel 
Instance details

Defined in Data.Time.Zones.DB

Generic TZLabel 
Instance details

Defined in Data.Time.Zones.DB

Associated Types

type Rep TZLabel :: Type -> Type #

Methods

from :: TZLabel -> Rep TZLabel x #

to :: Rep TZLabel x -> TZLabel #

Read TZLabel 
Instance details

Defined in Data.Time.Zones.DB

Show TZLabel 
Instance details

Defined in Data.Time.Zones.DB

NFData TZLabel 
Instance details

Defined in Data.Time.Zones.DB

Methods

rnf :: TZLabel -> () #

Eq TZLabel 
Instance details

Defined in Data.Time.Zones.DB

Methods

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

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

Ord TZLabel 
Instance details

Defined in Data.Time.Zones.DB

type Rep TZLabel 
Instance details

Defined in Data.Time.Zones.DB

type Rep TZLabel = D1 ('MetaData "TZLabel" "Data.Time.Zones.DB" "tzdata-0.2.20230322.0-KDyrO7pK7aLBWd0qwCokt0" 'False) (((((((((C1 ('MetaCons "Africa__Abidjan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Accra" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Addis_Ababa" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Algiers" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Africa__Asmara" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Asmera" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Bamako" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Africa__Bangui" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Banjul" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Africa__Bissau" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Blantyre" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Brazzaville" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Bujumbura" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Africa__Cairo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Casablanca" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Ceuta" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Africa__Conakry" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Dakar" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Africa__Dar_es_Salaam" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Djibouti" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Douala" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__El_Aaiun" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Africa__Freetown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Gaborone" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Harare" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Africa__Johannesburg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Juba" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Africa__Kampala" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Khartoum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Kigali" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Africa__Kinshasa" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Lagos" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Africa__Libreville" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Lome" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Luanda" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Africa__Lubumbashi" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Lusaka" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Africa__Malabo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Maputo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Maseru" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Mbabane" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Africa__Mogadishu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Monrovia" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Nairobi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Africa__Ndjamena" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Niamey" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Africa__Nouakchott" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Ouagadougou" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Porto_Novo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Sao_Tome" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Africa__Timbuktu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Africa__Tripoli" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Africa__Tunis" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Africa__Windhoek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Adak" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "America__Anchorage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Anguilla" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Antigua" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Araguaina" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Argentina__Buenos_Aires" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Argentina__Catamarca" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Argentina__ComodRivadavia" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Argentina__Cordoba" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Argentina__Jujuy" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Argentina__La_Rioja" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Argentina__Mendoza" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Argentina__Rio_Gallegos" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Argentina__Salta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Argentina__San_Juan" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "America__Argentina__San_Luis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Argentina__Tucuman" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Argentina__Ushuaia" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Aruba" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Asuncion" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "America__Atikokan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Atka" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Bahia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Bahia_Banderas" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Barbados" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Belem" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Belize" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Blanc_Sablon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Boa_Vista" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Bogota" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Boise" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Buenos_Aires" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Cambridge_Bay" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Campo_Grande" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Cancun" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Caracas" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Catamarca" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Cayenne" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "America__Cayman" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Chicago" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Chihuahua" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Ciudad_Juarez" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Coral_Harbour" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Cordoba" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Costa_Rica" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Creston" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Cuiaba" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Curacao" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Danmarkshavn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Dawson" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Dawson_Creek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Denver" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "America__Detroit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Dominica" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Edmonton" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Eirunepe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__El_Salvador" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "America__Ensenada" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Fort_Nelson" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Fort_Wayne" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Fortaleza" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Glace_Bay" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Godthab" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Goose_Bay" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Grand_Turk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Grenada" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Guadeloupe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Guatemala" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Guayaquil" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Guyana" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Halifax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "America__Havana" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Hermosillo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Indiana__Indianapolis" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Indiana__Knox" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Indiana__Marengo" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "America__Indiana__Petersburg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Indiana__Tell_City" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Indiana__Vevay" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Indiana__Vincennes" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Indiana__Winamac" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Indianapolis" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Inuvik" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Iqaluit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Jamaica" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Jujuy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Juneau" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Kentucky__Louisville" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Kentucky__Monticello" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Knox_IN" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "America__Kralendijk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__La_Paz" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Lima" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Los_Angeles" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Louisville" 'PrefixI 'False) (U1 :: Type -> Type))))))))) :+: (((((((C1 ('MetaCons "America__Lower_Princes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Maceio" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Managua" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Manaus" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Marigot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Martinique" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Matamoros" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Mazatlan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Mendoza" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Menominee" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Merida" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Metlakatla" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Mexico_City" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Miquelon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Moncton" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Monterrey" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Montevideo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Montreal" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "America__Montserrat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Nassau" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__New_York" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Nipigon" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Nome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Noronha" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__North_Dakota__Beulah" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__North_Dakota__Center" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__North_Dakota__New_Salem" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Nuuk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Ojinaga" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Panama" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Pangnirtung" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Paramaribo" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "America__Phoenix" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Port_au_Prince" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Port_of_Spain" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Porto_Acre" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Porto_Velho" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "America__Puerto_Rico" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Punta_Arenas" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Rainy_River" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Rankin_Inlet" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Recife" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Regina" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Resolute" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Rio_Branco" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Rosario" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Santa_Isabel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Santarem" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Santiago" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Santo_Domingo" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__Sao_Paulo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Scoresbysund" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Shiprock" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Sitka" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__St_Barthelemy" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "America__St_Johns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__St_Kitts" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__St_Lucia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__St_Thomas" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "America__St_Vincent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Swift_Current" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Tegucigalpa" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Thule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Thunder_Bay" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "America__Tijuana" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Toronto" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Tortola" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Vancouver" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Virgin" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "America__Whitehorse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "America__Winnipeg" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "America__Yakutat" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "America__Yellowknife" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Antarctica__Casey" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "Antarctica__Davis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Antarctica__DumontDUrville" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Antarctica__Macquarie" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Antarctica__Mawson" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Antarctica__McMurdo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Antarctica__Palmer" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Antarctica__Rothera" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Antarctica__South_Pole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Antarctica__Syowa" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Antarctica__Troll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Antarctica__Vostok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Arctic__Longyearbyen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Aden" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Asia__Almaty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Amman" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Anadyr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Aqtau" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Aqtobe" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Asia__Ashgabat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Ashkhabad" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Atyrau" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Baghdad" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Asia__Bahrain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Baku" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Bangkok" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Barnaul" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Beirut" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Asia__Bishkek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Brunei" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Calcutta" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Chita" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Choibalsan" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Asia__Chongqing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Chungking" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Colombo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Dacca" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Damascus" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Asia__Dhaka" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Dili" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Dubai" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Dushanbe" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Asia__Famagusta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Gaza" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Harbin" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Hebron" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Ho_Chi_Minh" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Asia__Hong_Kong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Hovd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Irkutsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Istanbul" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Jakarta" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Asia__Jayapura" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Jerusalem" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Kabul" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Kamchatka" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Karachi" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Asia__Kashgar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Kathmandu" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Katmandu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Khandyga" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Asia__Kolkata" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Krasnoyarsk" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Kuala_Lumpur" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Kuching" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Kuwait" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Asia__Macao" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Macau" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Magadan" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Makassar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Manila" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Asia__Muscat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Nicosia" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Novokuznetsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Novosibirsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Omsk" 'PrefixI 'False) (U1 :: Type -> Type)))))))))) :+: ((((((((C1 ('MetaCons "Asia__Oral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Phnom_Penh" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Pontianak" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Pyongyang" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Asia__Qatar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Qostanay" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Qyzylorda" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Rangoon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Riyadh" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Asia__Saigon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Sakhalin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Samarkand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Seoul" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Asia__Shanghai" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Singapore" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Srednekolymsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Taipei" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Tashkent" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Asia__Tbilisi" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Tehran" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Tel_Aviv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Thimbu" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Asia__Thimphu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Tokyo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Tomsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Ujung_Pandang" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Ulaanbaatar" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Asia__Ulan_Bator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Urumqi" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Ust_Nera" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Vientiane" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Vladivostok" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Asia__Yakutsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asia__Yangon" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asia__Yekaterinburg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asia__Yerevan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atlantic__Azores" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Atlantic__Bermuda" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atlantic__Canary" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Atlantic__Cape_Verde" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atlantic__Faeroe" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Atlantic__Faroe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atlantic__Jan_Mayen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Atlantic__Madeira" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Atlantic__Reykjavik" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atlantic__South_Georgia" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Atlantic__St_Helena" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atlantic__Stanley" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Australia__ACT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Adelaide" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Australia__Brisbane" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Broken_Hill" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Australia__Canberra" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Australia__Currie" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Darwin" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Australia__Eucla" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Hobart" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Australia__LHI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Lindeman" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Australia__Lord_Howe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Melbourne" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Australia__NSW" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Australia__North" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Perth" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Australia__Queensland" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__South" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Australia__Sydney" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Australia__Tasmania" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Victoria" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Australia__West" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Australia__Yancowinna" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Brazil__Acre" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Brazil__DeNoronha" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Brazil__East" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "Brazil__West" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CET" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CST6CDT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Canada__Atlantic" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Canada__Central" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Canada__Eastern" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Canada__Mountain" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Canada__Newfoundland" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Canada__Pacific" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Canada__Saskatchewan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Canada__Yukon" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Chile__Continental" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Chile__EasterIsland" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Cuba" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EET" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EST" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EST5EDT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Egypt" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Eire" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__GMT'0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT'1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Etc__GMT'10" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT'11" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__GMT'12" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Etc__GMT'2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT'3" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Etc__GMT'4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT'5" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__GMT'6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Etc__GMT'7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT'8" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Etc__GMT'9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT_0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__GMT_1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Etc__GMT_10" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT_11" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Etc__GMT_12" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT_13" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__GMT_14" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT_2" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Etc__GMT_3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT_4" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__GMT_5" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Etc__GMT_6" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT_7" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Etc__GMT_8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__GMT_9" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__GMT0" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Etc__Greenwich" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__UCT" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Etc__UTC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Etc__Universal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Etc__Zulu" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Amsterdam" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Andorra" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Europe__Astrakhan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Athens" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Belfast" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Belgrade" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Europe__Berlin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Bratislava" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Brussels" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Bucharest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Budapest" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Europe__Busingen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Chisinau" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Copenhagen" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Dublin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Gibraltar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Europe__Guernsey" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Helsinki" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Isle_of_Man" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Istanbul" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Jersey" 'PrefixI 'False) (U1 :: Type -> Type))))))))) :+: (((((((C1 ('MetaCons "Europe__Kaliningrad" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Kiev" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Kirov" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Kyiv" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Europe__Lisbon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Ljubljana" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__London" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Luxembourg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Madrid" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Europe__Malta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Mariehamn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Minsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Monaco" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Europe__Moscow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Nicosia" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Oslo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Paris" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Podgorica" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Europe__Prague" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Riga" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Rome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Samara" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Europe__San_Marino" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Sarajevo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Saratov" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Simferopol" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Skopje" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Europe__Sofia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Stockholm" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Tallinn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Tirane" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Tiraspol" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Europe__Ulyanovsk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Uzhgorod" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Vaduz" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Europe__Vatican" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Vienna" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Europe__Vilnius" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Volgograd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Europe__Warsaw" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Zagreb" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Europe__Zaporozhye" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Europe__Zurich" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Factory" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GB_Eire" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "GMT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GMT'0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GMT_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GMT0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Greenwich" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "HST" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Hongkong" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Iceland" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Indian__Antananarivo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Indian__Chagos" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Indian__Christmas" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Indian__Cocos" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Indian__Comoro" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Indian__Kerguelen" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Indian__Mahe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Indian__Maldives" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Indian__Mauritius" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Indian__Mayotte" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Indian__Reunion" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Iran" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Israel" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Jamaica" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Japan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Kwajalein" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Libya" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MET" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MST" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MST7MDT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mexico__BajaNorte" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "Mexico__BajaSur" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mexico__General" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NZ_CHAT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Navajo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PRC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PST8PDT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pacific__Apia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Auckland" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Pacific__Bougainville" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Chatham" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Chuuk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Easter" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Pacific__Efate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Enderbury" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Fakaofo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pacific__Fiji" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Funafuti" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Pacific__Galapagos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Gambier" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Guadalcanal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Guam" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Pacific__Honolulu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Johnston" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Kanton" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pacific__Kiritimati" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Kosrae" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Pacific__Kwajalein" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Majuro" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Marquesas" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pacific__Midway" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Nauru" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Pacific__Niue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Norfolk" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Noumea" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pacific__Pago_Pago" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Palau" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Pacific__Pitcairn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Pohnpei" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Ponape" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Port_Moresby" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Pacific__Rarotonga" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Saipan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Samoa" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pacific__Tahiti" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Tarawa" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Pacific__Tongatapu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Truk" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pacific__Wake" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pacific__Wallis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pacific__Yap" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Poland" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Portugal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ROC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ROK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Singapore" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Turkey" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UCT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "US__Alaska" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "US__Aleutian" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "US__Arizona" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "US__Central" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "US__East_Indiana" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "US__Eastern" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "US__Hawaii" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "US__Indiana_Starke" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "US__Michigan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "US__Mountain" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "US__Pacific" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "US__Samoa" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "UTC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Universal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "W_SU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WET" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Zulu" 'PrefixI 'False) (U1 :: Type -> Type)))))))))))