{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NoImplicitPrelude          #-}
{-# LANGUAGE OverloadedStrings          #-}

-- |

-- Module      : Web.Google.Maps.Common

-- Description : Common to the Google Maps Platform

-- Copyright   : (c) Mike Pilgrem 2017, 2018, 2021

-- Maintainer  : public@pilgrem.com

-- Stability   : experimental

--

-- This module has no connection with Google Inc. or its affiliates.

module Web.Google.Maps.Common
  ( -- * Functions

    googleMapsApis
    -- * Types

  , Address  (..)
  , Key      (..)
  , Language (..)
  , LatLng   (..)
  , Location (..)
  , Region   (..)
  ) where

import           Data.Aeson ( FromJSON )
import           Data.Double.Conversion.Text ( toFixed )
import           Data.Eq ( Eq )
import           Data.Function ( ($) )
import           Data.List ( intersperse, map )
import           Data.Text ( Text )
import qualified Data.Text as T ( concat )
import           GHC.Exts ( Double )
import           GHC.Generics ( Generic )
import           Servant.API ( ToHttpApiData (..) )
import           Servant.Client ( BaseUrl (..), Scheme (..) )
import           Text.Show ( Show )

-- | API key

newtype Key = Key Text
  deriving (Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
/= :: Key -> Key -> Bool
Eq, Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
(Int -> Key -> ShowS)
-> (Key -> String) -> ([Key] -> ShowS) -> Show Key
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Key -> ShowS
showsPrec :: Int -> Key -> ShowS
$cshow :: Key -> String
show :: Key -> String
$cshowList :: [Key] -> ShowS
showList :: [Key] -> ShowS
Show, Key -> ByteString
Key -> Text
Key -> Builder
(Key -> Text)
-> (Key -> Builder)
-> (Key -> ByteString)
-> (Key -> Text)
-> (Key -> Builder)
-> ToHttpApiData Key
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: Key -> Text
toUrlPiece :: Key -> Text
$ctoEncodedUrlPiece :: Key -> Builder
toEncodedUrlPiece :: Key -> Builder
$ctoHeader :: Key -> ByteString
toHeader :: Key -> ByteString
$ctoQueryParam :: Key -> Text
toQueryParam :: Key -> Text
$ctoEncodedQueryParam :: Key -> Builder
toEncodedQueryParam :: Key -> Builder
ToHttpApiData)

-- | Location

data Location
  = Coords LatLng
  | Locale Address
  deriving (Location -> Location -> Bool
(Location -> Location -> Bool)
-> (Location -> Location -> Bool) -> Eq Location
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Location -> Location -> Bool
== :: Location -> Location -> Bool
$c/= :: Location -> Location -> Bool
/= :: Location -> Location -> Bool
Eq, Int -> Location -> ShowS
[Location] -> ShowS
Location -> String
(Int -> Location -> ShowS)
-> (Location -> String) -> ([Location] -> ShowS) -> Show Location
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Location -> ShowS
showsPrec :: Int -> Location -> ShowS
$cshow :: Location -> String
show :: Location -> String
$cshowList :: [Location] -> ShowS
showList :: [Location] -> ShowS
Show)

instance ToHttpApiData Location where
  toUrlPiece :: Location -> Text
toUrlPiece Location
location
    | Coords LatLng
latlng <- Location
location
      = LatLng -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece LatLng
latlng
    | Locale Address
address <- Location
location
      = Address -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece Address
address

instance ToHttpApiData [Location] where
  toUrlPiece :: [Location] -> Text
toUrlPiece [] = Text
""
  toUrlPiece [Location]
ls = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"|" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Location -> Text) -> [Location] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Location -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece [Location]
ls

-- | Latitude and longitude: precision beyond 6 decimal places is ignored.

data LatLng = LatLng
  { LatLng -> Double
lat :: Double  -- ^ Takes any value between -90 and 90.

  , LatLng -> Double
lng :: Double  -- ^ Takes any value between -180 and 180.

  } deriving (LatLng -> LatLng -> Bool
(LatLng -> LatLng -> Bool)
-> (LatLng -> LatLng -> Bool) -> Eq LatLng
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LatLng -> LatLng -> Bool
== :: LatLng -> LatLng -> Bool
$c/= :: LatLng -> LatLng -> Bool
/= :: LatLng -> LatLng -> Bool
Eq, Int -> LatLng -> ShowS
[LatLng] -> ShowS
LatLng -> String
(Int -> LatLng -> ShowS)
-> (LatLng -> String) -> ([LatLng] -> ShowS) -> Show LatLng
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LatLng -> ShowS
showsPrec :: Int -> LatLng -> ShowS
$cshow :: LatLng -> String
show :: LatLng -> String
$cshowList :: [LatLng] -> ShowS
showList :: [LatLng] -> ShowS
Show, (forall x. LatLng -> Rep LatLng x)
-> (forall x. Rep LatLng x -> LatLng) -> Generic LatLng
forall x. Rep LatLng x -> LatLng
forall x. LatLng -> Rep LatLng x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LatLng -> Rep LatLng x
from :: forall x. LatLng -> Rep LatLng x
$cto :: forall x. Rep LatLng x -> LatLng
to :: forall x. Rep LatLng x -> LatLng
Generic)

instance ToHttpApiData LatLng where
  toUrlPiece :: LatLng -> Text
toUrlPiece (LatLng Double
lat' Double
lng')
    = [Text] -> Text
T.concat [Int -> Double -> Text
toFixed Int
precision Double
lat', Text
",", Int -> Double -> Text
toFixed Int
precision Double
lng']
   where
    precision :: Int
precision = Int
6  -- Precision beyond 6 decimal places is ignored.


instance FromJSON LatLng

-- | Address

newtype Address = Address Text
  deriving (Address -> Address -> Bool
(Address -> Address -> Bool)
-> (Address -> Address -> Bool) -> Eq Address
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Address -> Address -> Bool
== :: Address -> Address -> Bool
$c/= :: Address -> Address -> Bool
/= :: Address -> Address -> Bool
Eq, Int -> Address -> ShowS
[Address] -> ShowS
Address -> String
(Int -> Address -> ShowS)
-> (Address -> String) -> ([Address] -> ShowS) -> Show Address
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Address -> ShowS
showsPrec :: Int -> Address -> ShowS
$cshow :: Address -> String
show :: Address -> String
$cshowList :: [Address] -> ShowS
showList :: [Address] -> ShowS
Show, Address -> ByteString
Address -> Text
Address -> Builder
(Address -> Text)
-> (Address -> Builder)
-> (Address -> ByteString)
-> (Address -> Text)
-> (Address -> Builder)
-> ToHttpApiData Address
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: Address -> Text
toUrlPiece :: Address -> Text
$ctoEncodedUrlPiece :: Address -> Builder
toEncodedUrlPiece :: Address -> Builder
$ctoHeader :: Address -> ByteString
toHeader :: Address -> ByteString
$ctoQueryParam :: Address -> Text
toQueryParam :: Address -> Text
$ctoEncodedQueryParam :: Address -> Builder
toEncodedQueryParam :: Address -> Builder
ToHttpApiData)

-- | Language: supported languages based on the list at

-- <https://developers.google.com/maps/faq#languagesupport> (as at 27 October

-- 2024).

data Language
  = Afrikaans -- ^ @since 0.7.0.0

  | Albanian
  | Amharic -- ^ @since 0.7.0.0

  | Arabic
  | Armenian -- ^ @since 0.7.0.0

  | Azerbaijani -- ^ @since 0.7.0.0

  | Basque
  | Belarusian
  | Bengali
  | Bosnian -- ^ @since 0.7.0.0

  | Bulgarian
  | Burmese
  | Catalan
  | Chinese -- ^ @since 0.7.0.0

  | ChineseSimplified
  | ChineseHongKong -- ^ @since 0.7.0.0

  | ChineseTraditional
  | Croatian
  | Czech
  | Danish
  | Dutch
  | English
  | EnglishAustralian
  | EnglishBritish
  | Estonian -- ^ @since 0.7.0.0

  | Farsi
  | Filipino
  | Finnish
  | French
  | FrenchCanadian -- ^ @since 0.7.0.0

  | Galician
  | Georgian -- ^ @since 0.7.0.0

  | German
  | Greek
  | Gujarati
  | Hebrew
  | Hindi
  | Hungarian
  | Icelandic -- ^ @since 0.7.0.0

  | Indonesian
  | Italian
  | Japanese
  | Kannada
  | Kazakh
  | Khmer -- ^ @since 0.7.0.0

  | Korean
  | Kyrgyz
  | Lao -- ^ @since 0.7.0.0

  | Latvian
  | Lithuanian
  | Macedonian
  | Malay -- ^ @since 0.7.0.0

  | Malayalam
  | Marathi
  | Mongolian -- ^ @since 0.7.0.0

  | Nepali -- ^ @since 0.7.0.0

  | Norwegian
  | Polish
  | Portuguese
  | PortugueseBrazil
  | PortuguesePortugal
  | Punjabi
  | Romanian
  | Russian
  | Serbian
  | Sinhalese -- ^ @since 0.7.0.0

  | Slovak
  | Slovenian
  | Spanish
  | SpanishLatinAmerican -- ^ @since 0.7.0.0

  | Swahili -- ^ @since 0.7.0.0

  | Swedish
  | Tagalog -- ^ No longer listed by Google at 12 June 2021. See 'Filipino'.

  | Tamil
  | Telugu
  | Thai
  | Turkish
  | Ukrainian
  | Urdu -- ^ @since 0.7.0.0

  | Uzbek
  | Vietnamese
  | Zulu -- ^ @since 0.7.0.0

  deriving (Language -> Language -> Bool
(Language -> Language -> Bool)
-> (Language -> Language -> Bool) -> Eq Language
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Language -> Language -> Bool
== :: Language -> Language -> Bool
$c/= :: Language -> Language -> Bool
/= :: Language -> Language -> Bool
Eq, Int -> Language -> ShowS
[Language] -> ShowS
Language -> String
(Int -> Language -> ShowS)
-> (Language -> String) -> ([Language] -> ShowS) -> Show Language
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Language -> ShowS
showsPrec :: Int -> Language -> ShowS
$cshow :: Language -> String
show :: Language -> String
$cshowList :: [Language] -> ShowS
showList :: [Language] -> ShowS
Show)

instance ToHttpApiData Language where
  toUrlPiece :: Language -> Text
toUrlPiece Language
language = case Language
language of
    Language
Afrikaans            -> Text
"af"
    Language
Albanian             -> Text
"sq"
    Language
Amharic              -> Text
"am"
    Language
Arabic               -> Text
"ar"
    Language
Armenian             -> Text
"hy"
    Language
Azerbaijani          -> Text
"az"
    Language
Basque               -> Text
"eu"
    Language
Belarusian           -> Text
"be"
    Language
Bengali              -> Text
"bn"
    Language
Bosnian              -> Text
"bs"
    Language
Bulgarian            -> Text
"bg"
    Language
Burmese              -> Text
"my"
    Language
Catalan              -> Text
"ca"
    Language
Chinese              -> Text
"zh"
    Language
ChineseSimplified    -> Text
"zh-CN"
    Language
ChineseHongKong      -> Text
"zh-HK"
    Language
ChineseTraditional   -> Text
"zh-TW"
    Language
Croatian             -> Text
"hr"
    Language
Czech                -> Text
"cs"
    Language
Danish               -> Text
"da"
    Language
Dutch                -> Text
"nl"
    Language
English              -> Text
"en"
    Language
EnglishAustralian    -> Text
"en-AU"
    Language
EnglishBritish       -> Text
"en-GB"
    Language
Estonian             -> Text
"et"
    Language
Farsi                -> Text
"fa"
    Language
Filipino             -> Text
"fil"
    Language
Finnish              -> Text
"fi"
    Language
French               -> Text
"fr"
    Language
FrenchCanadian       -> Text
"fr-CA"
    Language
Galician             -> Text
"gl"
    Language
Georgian             -> Text
"ka"
    Language
German               -> Text
"de"
    Language
Greek                -> Text
"el"
    Language
Gujarati             -> Text
"gu"
    Language
Hebrew               -> Text
"iw"
    Language
Hindi                -> Text
"hi"
    Language
Hungarian            -> Text
"hu"
    Language
Icelandic            -> Text
"is"
    Language
Indonesian           -> Text
"id"
    Language
Italian              -> Text
"it"
    Language
Japanese             -> Text
"ja"
    Language
Kannada              -> Text
"kn"
    Language
Kazakh               -> Text
"kk"
    Language
Khmer                -> Text
"km"
    Language
Korean               -> Text
"ko"
    Language
Kyrgyz               -> Text
"ky"
    Language
Lao                  -> Text
"lo"
    Language
Latvian              -> Text
"lv"
    Language
Lithuanian           -> Text
"lt"
    Language
Macedonian           -> Text
"mk"
    Language
Malay                -> Text
"ms"
    Language
Malayalam            -> Text
"ml"
    Language
Marathi              -> Text
"mr"
    Language
Mongolian            -> Text
"mn"
    Language
Nepali               -> Text
"ne"
    Language
Norwegian            -> Text
"no"
    Language
Polish               -> Text
"pl"
    Language
Portuguese           -> Text
"pt"
    Language
PortugueseBrazil     -> Text
"pt-BR"
    Language
PortuguesePortugal   -> Text
"pt-PT"
    Language
Punjabi              -> Text
"pa"
    Language
Romanian             -> Text
"ro"
    Language
Russian              -> Text
"ru"
    Language
Serbian              -> Text
"sr"
    Language
Sinhalese            -> Text
"si"
    Language
Slovak               -> Text
"sk"
    Language
Slovenian            -> Text
"sl"
    Language
Spanish              -> Text
"es"
    Language
SpanishLatinAmerican -> Text
"es-419"
    Language
Swahili              -> Text
"sw"
    Language
Swedish              -> Text
"sv"
    Language
Tagalog              -> Text
"tl"
    Language
Tamil                -> Text
"ta"
    Language
Telugu               -> Text
"te"
    Language
Thai                 -> Text
"th"
    Language
Turkish              -> Text
"tr"
    Language
Ukrainian            -> Text
"uk"
    Language
Urdu                 -> Text
"ur"
    Language
Uzbek                -> Text
"uz"
    Language
Vietnamese           -> Text
"vi"
    Language
Zulu                 -> Text
"zu"

-- | Region: a ccTLD (country code top level domain).

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

  | UK -- United Kingdom of Great Britain and Northern Ireland

  | EU -- European Union

  deriving (Region -> Region -> Bool
(Region -> Region -> Bool)
-> (Region -> Region -> Bool) -> Eq Region
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Region -> Region -> Bool
== :: Region -> Region -> Bool
$c/= :: Region -> Region -> Bool
/= :: Region -> Region -> Bool
Eq, Int -> Region -> ShowS
[Region] -> ShowS
Region -> String
(Int -> Region -> ShowS)
-> (Region -> String) -> ([Region] -> ShowS) -> Show Region
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Region -> ShowS
showsPrec :: Int -> Region -> ShowS
$cshow :: Region -> String
show :: Region -> String
$cshowList :: [Region] -> ShowS
showList :: [Region] -> ShowS
Show)

instance ToHttpApiData Region where
  toUrlPiece :: Region -> Text
toUrlPiece Region
region = case Region
region of
    Region
AD -> Text
"ad"
    Region
AE -> Text
"ae"
    Region
AF -> Text
"af"
    Region
AG -> Text
"ag"
    Region
AI -> Text
"ai"
    Region
AL -> Text
"al"
    Region
AM -> Text
"am"
    Region
AO -> Text
"ao"
    Region
AQ -> Text
"aq"
    Region
AR -> Text
"ar"
    Region
AS -> Text
"as"
    Region
AT -> Text
"at"
    Region
AU -> Text
"au"
    Region
AW -> Text
"aw"
    Region
AX -> Text
"ax"
    Region
AZ -> Text
"az"
    Region
BA -> Text
"ba"
    Region
BB -> Text
"bb"
    Region
BD -> Text
"bd"
    Region
BE -> Text
"be"
    Region
BF -> Text
"bf"
    Region
BG -> Text
"bg"
    Region
BH -> Text
"bh"
    Region
BI -> Text
"bi"
    Region
BJ -> Text
"bj"
    Region
BL -> Text
"bl"
    Region
BM -> Text
"bm"
    Region
BN -> Text
"bn"
    Region
BO -> Text
"bo"
    Region
BQ -> Text
"bq"
    Region
BR -> Text
"br"
    Region
BS -> Text
"bs"
    Region
BT -> Text
"bt"
    Region
BV -> Text
"bv"
    Region
BW -> Text
"bw"
    Region
BY -> Text
"by"
    Region
BZ -> Text
"bz"
    Region
CA -> Text
"ca"
    Region
CC -> Text
"cc"
    Region
CD -> Text
"cd"
    Region
CF -> Text
"cf"
    Region
CG -> Text
"cg"
    Region
CH -> Text
"ch"
    Region
CI -> Text
"ci"
    Region
CK -> Text
"ck"
    Region
CL -> Text
"cl"
    Region
CM -> Text
"cm"
    Region
CN -> Text
"cn"
    Region
CO -> Text
"co"
    Region
CR -> Text
"cr"
    Region
CU -> Text
"cu"
    Region
CV -> Text
"cv"
    Region
CW -> Text
"cw"
    Region
CX -> Text
"cx"
    Region
CY -> Text
"cy"
    Region
CZ -> Text
"cz"
    Region
DE -> Text
"de"
    Region
DJ -> Text
"dj"
    Region
DK -> Text
"dk"
    Region
DM -> Text
"dm"
    Region
DO -> Text
"do"
    Region
DZ -> Text
"dz"
    Region
EC -> Text
"ec"
    Region
EE -> Text
"ee"
    Region
EG -> Text
"eg"
    Region
EH -> Text
"eh"
    Region
ER -> Text
"er"
    Region
ES -> Text
"es"
    Region
ET -> Text
"et"
    Region
FI -> Text
"fi"
    Region
FJ -> Text
"fj"
    Region
FK -> Text
"fk"
    Region
FM -> Text
"fm"
    Region
FO -> Text
"fo"
    Region
FR -> Text
"fr"
    Region
GA -> Text
"ga"
    Region
GB -> Text
"gb"
    Region
GD -> Text
"gd"
    Region
GE -> Text
"ge"
    Region
GF -> Text
"gf"
    Region
GG -> Text
"gg"
    Region
GH -> Text
"gh"
    Region
GI -> Text
"gi"
    Region
GL -> Text
"gl"
    Region
GM -> Text
"gm"
    Region
GN -> Text
"gn"
    Region
GP -> Text
"gp"
    Region
GQ -> Text
"gq"
    Region
GR -> Text
"gr"
    Region
GS -> Text
"gs"
    Region
GT -> Text
"gt"
    Region
GU -> Text
"gu"
    Region
GW -> Text
"gw"
    Region
GY -> Text
"gy"
    Region
HK -> Text
"hk"
    Region
HM -> Text
"hm"
    Region
HN -> Text
"hn"
    Region
HR -> Text
"hr"
    Region
HT -> Text
"ht"
    Region
HU -> Text
"hu"
    Region
ID -> Text
"id"
    Region
IE -> Text
"ie"
    Region
IL -> Text
"il"
    Region
IM -> Text
"im"
    Region
IN -> Text
"in"
    Region
IO -> Text
"io"
    Region
IQ -> Text
"iq"
    Region
IR -> Text
"ir"
    Region
IS -> Text
"is"
    Region
IT -> Text
"it"
    Region
JE -> Text
"je"
    Region
JM -> Text
"jm"
    Region
JO -> Text
"jo"
    Region
JP -> Text
"jp"
    Region
KE -> Text
"ke"
    Region
KG -> Text
"kg"
    Region
KH -> Text
"kh"
    Region
KI -> Text
"ki"
    Region
KM -> Text
"km"
    Region
KN -> Text
"kn"
    Region
KP -> Text
"kp"
    Region
KR -> Text
"kr"
    Region
KW -> Text
"kw"
    Region
KY -> Text
"ky"
    Region
KZ -> Text
"kz"
    Region
LA -> Text
"la"
    Region
LB -> Text
"lb"
    Region
LC -> Text
"lc"
    Region
LI -> Text
"li"
    Region
LK -> Text
"lk"
    Region
LR -> Text
"lr"
    Region
LS -> Text
"ls"
    Region
LT -> Text
"lt"
    Region
LU -> Text
"lu"
    Region
LV -> Text
"lv"
    Region
LY -> Text
"ly"
    Region
MA -> Text
"ma"
    Region
MC -> Text
"mc"
    Region
MD -> Text
"md"
    Region
ME -> Text
"me"
    Region
MF -> Text
"mf"
    Region
MG -> Text
"mg"
    Region
MH -> Text
"mh"
    Region
MK -> Text
"mk"
    Region
ML -> Text
"ml"
    Region
MM -> Text
"mm"
    Region
MN -> Text
"mn"
    Region
MO -> Text
"mo"
    Region
MP -> Text
"mp"
    Region
MQ -> Text
"mq"
    Region
MR -> Text
"mr"
    Region
MS -> Text
"ms"
    Region
MT -> Text
"mt"
    Region
MU -> Text
"mu"
    Region
MV -> Text
"mv"
    Region
MW -> Text
"mw"
    Region
MX -> Text
"mx"
    Region
MY -> Text
"my"
    Region
MZ -> Text
"mz"
    Region
NA -> Text
"na"
    Region
NC -> Text
"nc"
    Region
NE -> Text
"ne"
    Region
NF -> Text
"nf"
    Region
NG -> Text
"ng"
    Region
NI -> Text
"ni"
    Region
NL -> Text
"nl"
    Region
NO -> Text
"no"
    Region
NP -> Text
"np"
    Region
NR -> Text
"nr"
    Region
NU -> Text
"nu"
    Region
NZ -> Text
"nz"
    Region
OM -> Text
"om"
    Region
PA -> Text
"pa"
    Region
PE -> Text
"pe"
    Region
PF -> Text
"pf"
    Region
PG -> Text
"pg"
    Region
PH -> Text
"ph"
    Region
PK -> Text
"pk"
    Region
PL -> Text
"pl"
    Region
PM -> Text
"pm"
    Region
PN -> Text
"pn"
    Region
PR -> Text
"pr"
    Region
PS -> Text
"ps"
    Region
PT -> Text
"pt"
    Region
PW -> Text
"pw"
    Region
PY -> Text
"py"
    Region
QA -> Text
"qa"
    Region
RE -> Text
"re"
    Region
RO -> Text
"ro"
    Region
RS -> Text
"rs"
    Region
RU -> Text
"ru"
    Region
RW -> Text
"rw"
    Region
SA -> Text
"sa"
    Region
SB -> Text
"sb"
    Region
SC -> Text
"sc"
    Region
SD -> Text
"sd"
    Region
SE -> Text
"se"
    Region
SG -> Text
"sg"
    Region
SH -> Text
"sh"
    Region
SI -> Text
"si"
    Region
SJ -> Text
"sj"
    Region
SK -> Text
"sk"
    Region
SL -> Text
"sl"
    Region
SM -> Text
"sm"
    Region
SN -> Text
"sn"
    Region
SO -> Text
"so"
    Region
SR -> Text
"sr"
    Region
SS -> Text
"ss"
    Region
ST -> Text
"st"
    Region
SV -> Text
"sv"
    Region
SX -> Text
"sx"
    Region
SY -> Text
"sy"
    Region
SZ -> Text
"sz"
    Region
TC -> Text
"tc"
    Region
TD -> Text
"td"
    Region
TF -> Text
"tf"
    Region
TG -> Text
"tg"
    Region
TH -> Text
"th"
    Region
TJ -> Text
"tj"
    Region
TK -> Text
"tk"
    Region
TL -> Text
"tl"
    Region
TM -> Text
"tm"
    Region
TN -> Text
"tn"
    Region
TO -> Text
"to"
    Region
TR -> Text
"tr"
    Region
TT -> Text
"tt"
    Region
TV -> Text
"tv"
    Region
TW -> Text
"tw"
    Region
TZ -> Text
"tz"
    Region
UA -> Text
"ua"
    Region
UG -> Text
"ug"
    Region
UM -> Text
"um"
    Region
US -> Text
"us"
    Region
UY -> Text
"uy"
    Region
UZ -> Text
"uz"
    Region
VA -> Text
"va"
    Region
VC -> Text
"vc"
    Region
VE -> Text
"ve"
    Region
VG -> Text
"vg"
    Region
VI -> Text
"vi"
    Region
VN -> Text
"vn"
    Region
VU -> Text
"vu"
    Region
WF -> Text
"wf"
    Region
WS -> Text
"ws"
    Region
YE -> Text
"ye"
    Region
YT -> Text
"yt"
    Region
ZA -> Text
"za"
    Region
ZM -> Text
"zm"
    Region
ZW -> Text
"zw"
    Region
AC -> Text
"ac" -- Saint Helena, Ascension and Tristan da Cunha

    Region
UK -> Text
"uk" -- United Kingdom of Great Britain and Northern Ireland

    Region
EU -> Text
"eu" -- European Union


-- | The base URL for the Google Maps Platform APIs.

googleMapsApis :: BaseUrl
googleMapsApis :: BaseUrl
googleMapsApis = Scheme -> String -> Int -> String -> BaseUrl
BaseUrl Scheme
Https String
"maps.googleapis.com" Int
443 String
"/maps/api"