Copyright | (c) Mike Pilgrem 2017 2018 |
---|---|
Maintainer | public@pilgrem.com |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module has no connection with Google Inc. or its affiliates.
The Google Maps Static API returns a map as an image via an HTTP request. This library provides bindings in Haskell to that API (version 2).
NB: The use of the Google Maps Static API services is subject to the Google Maps Platform Terms of Service, which terms restrict the use of content. End Users' use of Google Maps is subject to the then-current Google Maps/Google Earth Additional Terms of Service at https://maps.google.com/help/terms_maps.html and Google Privacy Policy at https://www.google.com/policies/privacy/.
The following are not yet implemented: non-PNG image formats; and encoded polyline paths.
The code below is an example console application to test the use of the library with the Google Maps Static API.
{-# LANGUAGE OverloadedStrings #-} module Main (main) where import Data.Maybe (fromJust) import Graphics.Gloss (Display (..), display, white) -- package gloss import Graphics.Gloss.Juicy (fromDynamicImage) -- package gloss-juicy import Network.HTTP.Client (newManager) import Network.HTTP.Client.TLS (tlsManagerSettings) import Web.Google.Maps.Static (Center (..), Key (..), Location (..), Size (..), staticmap, StaticmapResponse (..), Zoom (..)) main :: IO () main = do putStrLn $ "A test of the Google Maps Static API.\nNB: The use of " ++ "the API services is subject to the Google Maps Platform Terms of " ++ "Serivce at https://cloud.google.com/maps-platform/terms/.\n" mgr <- newManager tlsManagerSettings let apiKey = Key "<REPLACE_THIS_WITH_YOUR_ACTUAL_GOOGLE_API_KEY>" -- If using a digital signature ... secret = Just $ Secret "<REPLACE_THIS_WITH_YOUR_ACTUAL_GOOGLE_URL_SIGNING_SECRET>" center = Just $ Center (Location 42.165950 (-71.362015)) zoom = Just $ Zoom 17 w = 400 h = 400 size = Size w h result <- staticmap mgr apiKey secret center zoom size Nothing Nothing [] Nothing Nothing Nothing [] [] Nothing case result of Right response -> do let picture = fromJust $ fromDynamicImage response title = "Test Google Maps Static API" window = InWindow title (w, h) (10, 10) display window white picture Left err -> putStrLn $ "Error! Result:\n" ++ show err
Synopsis
- staticmap :: Manager -> Key -> Maybe Secret -> Maybe Center -> Maybe Zoom -> Size -> Maybe Scale -> Maybe Format -> [MapStyle] -> Maybe MapType -> Maybe Language -> Maybe Region -> [Markers] -> [Path] -> Maybe Visible -> IO (Either ClientError StaticmapResponse)
- type GoogleMapsStaticAPI = "staticmap" :> (QueryParam "key" Key :> (QueryParam "center" Center :> (QueryParam "zoom" Zoom :> (QueryParam "size" Size :> (QueryParam "scale" Scale :> (QueryParam "format" Format :> (QueryParams "style" MapStyle :> (QueryParam "maptype" MapType :> (QueryParam "language" Language :> (QueryParam "region" Region :> (QueryParams "markers" Markers :> (QueryParams "path" Path :> (QueryParam "visible" Visible :> (QueryParam "signature" Signature :> Get '[PNG] StaticmapResponse))))))))))))))
- api :: Proxy GoogleMapsStaticAPI
- newtype Key = Key Text
- newtype Secret = Secret Text
- newtype Signature = Signature Text
- newtype Center = Center Location
- data Location
- data LatLng = LatLng {}
- newtype Address = Address Text
- newtype Zoom = Zoom Int
- data Size = Size {}
- data Scale
- data Format
- data MapStyle = MapStyle (Maybe Feature) (Maybe Element) [MapStyleOp]
- data Feature
- = AllFeatures
- | Administrative
- | AdministrativeCountry
- | AdministrativeLandParcel
- | AdministrativeLocality
- | AdministrativeNeighborhood
- | AdministrativeProvince
- | Landscape
- | LandscapeManMade
- | LandscapeNatural
- | LandscapeNaturalLandcover
- | LandscapeNaturalTerrain
- | Poi
- | PoiAttraction
- | PoiBusiness
- | PoiGovernment
- | PoiMedical
- | PoiPark
- | PoiPlaceOfWorship
- | PoiSchool
- | PoiSportsComplex
- | Road
- | RoadArterial
- | RoadHighway
- | RoadHighwayControlledAccess
- | RoadLocal
- | Transit
- | TransitLine
- | TransitStation
- | TransitStationAirport
- | TransitStationBus
- | TransitStationRail
- | Water
- data Element
- data MapStyleOp
- data Visibility
- = On
- | Off
- | Simplified
- data MapType
- data Language
- = Afrikaans
- | Albanian
- | Amharic
- | Arabic
- | Armenian
- | Azerbaijani
- | Basque
- | Belarusian
- | Bengali
- | Bosnian
- | Bulgarian
- | Burmese
- | Catalan
- | Chinese
- | ChineseSimplified
- | ChineseHongKong
- | ChineseTraditional
- | Croatian
- | Czech
- | Danish
- | Dutch
- | English
- | EnglishAustralian
- | EnglishBritish
- | Estonian
- | Farsi
- | Filipino
- | Finnish
- | French
- | FrenchCanadian
- | Galician
- | Georgian
- | German
- | Greek
- | Gujarati
- | Hebrew
- | Hindi
- | Icelandic
- | Hungarian
- | Indonesian
- | Italian
- | Japanese
- | Kannada
- | Kazakh
- | Khmer
- | Korean
- | Kyrgyz
- | Lao
- | Latvian
- | Lithuanian
- | Macedonian
- | Malay
- | Malayalam
- | Marathi
- | Mongolian
- | Nepali
- | Norwegian
- | Polish
- | Portuguese
- | PortugueseBrazil
- | PortuguesePortugal
- | Punjabi
- | Romanian
- | Russian
- | Serbian
- | Sinhalese
- | Slovak
- | Slovenian
- | Spanish
- | SpanishLatinAmerican
- | Swahili
- | Swedish
- | Tagalog
- | Tamil
- | Telugu
- | Thai
- | Turkish
- | Ukrainian
- | Urdu
- | Uzbek
- | Vietnamese
- | Zulu
- data Region
- = AD
- | 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
- | UK
- | EU
- data Markers = Markers (Maybe MarkerStyle) [Location]
- data MarkerStyle
- = StdMarkerStyle { }
- | CustomIcon { }
- data MarkerSize
- data MarkerColor
- newtype MarkerLabel = MarkerLabel Char
- data StdColor
- data URI = URI {}
- data URIAuth = URIAuth {
- uriUserInfo :: String
- uriRegName :: String
- uriPort :: String
- data Anchor
- data StdAnchor
- data Path = Path (Maybe PathStyle) [Location]
- data PathStyle = PathStyle {}
- newtype PathWeight = PathWeight Int
- data PathColor
- newtype PathGeodesic = PathGeodesic Bool
- newtype Visible = Visible [Location]
- type StaticmapResponse = DynamicImage
Functions
staticmap :: Manager -> Key -> Maybe Secret -> Maybe Center -> Maybe Zoom -> Size -> Maybe Scale -> Maybe Format -> [MapStyle] -> Maybe MapType -> Maybe Language -> Maybe Region -> [Markers] -> [Path] -> Maybe Visible -> IO (Either ClientError StaticmapResponse) Source #
Retrieve a static map. NB: The use of the Google Maps Static API services is subject to the Google Maps Platform Terms of Service. End Users' use of Google Maps is subject to the then-current Google Maps/Google Earth Additional Terms of Service at https://maps.google.com/help/terms_maps.html and Google Privacy Policy at https://www.google.com/policies/privacy/.
API
type GoogleMapsStaticAPI = "staticmap" :> (QueryParam "key" Key :> (QueryParam "center" Center :> (QueryParam "zoom" Zoom :> (QueryParam "size" Size :> (QueryParam "scale" Scale :> (QueryParam "format" Format :> (QueryParams "style" MapStyle :> (QueryParam "maptype" MapType :> (QueryParam "language" Language :> (QueryParam "region" Region :> (QueryParams "markers" Markers :> (QueryParams "path" Path :> (QueryParam "visible" Visible :> (QueryParam "signature" Signature :> Get '[PNG] StaticmapResponse)))))))))))))) Source #
Google Maps Static API
api :: Proxy GoogleMapsStaticAPI Source #
API type
Types
API key
Instances
Show Key Source # | |
Eq Key Source # | |
ToHttpApiData Key Source # | |
Defined in Web.Google.Maps.Common toUrlPiece :: Key -> Text # toEncodedUrlPiece :: Key -> Builder # toHeader :: Key -> ByteString # toQueryParam :: Key -> Text # |
Secret for digital signature
Signature
Instances
Show Signature Source # | |
Eq Signature Source # | |
ToHttpApiData Signature Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Signature -> Text # toEncodedUrlPiece :: Signature -> Builder # toHeader :: Signature -> ByteString # toQueryParam :: Signature -> Text # |
Center of the map: not required if the map includes markers or paths.
Instances
Show Center Source # | |
Eq Center Source # | |
ToHttpApiData Center Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Center -> Text # toEncodedUrlPiece :: Center -> Builder # toHeader :: Center -> ByteString # toQueryParam :: Center -> Text # |
Location
Instances
Show Location Source # | |
Eq Location Source # | |
ToHttpApiData Location Source # | |
Defined in Web.Google.Maps.Common toUrlPiece :: Location -> Text # toEncodedUrlPiece :: Location -> Builder # toHeader :: Location -> ByteString # toQueryParam :: Location -> Text # | |
ToHttpApiData [Location] Source # | |
Defined in Web.Google.Maps.Common toUrlPiece :: [Location] -> Text # toEncodedUrlPiece :: [Location] -> Builder # toHeader :: [Location] -> ByteString # toQueryParam :: [Location] -> Text # |
Latitude and longitude: precision beyond 6 decimal places is ignored.
Instances
FromJSON LatLng Source # | |
Generic LatLng Source # | |
Show LatLng Source # | |
Eq LatLng Source # | |
ToHttpApiData LatLng Source # | |
Defined in Web.Google.Maps.Common toUrlPiece :: LatLng -> Text # toEncodedUrlPiece :: LatLng -> Builder # toHeader :: LatLng -> ByteString # toQueryParam :: LatLng -> Text # | |
type Rep LatLng Source # | |
Defined in Web.Google.Maps.Common type Rep LatLng = D1 ('MetaData "LatLng" "Web.Google.Maps.Common" "google-static-maps-0.7.0.2-Gdbwzt23wN2L0WYJarjNP8" 'False) (C1 ('MetaCons "LatLng" 'PrefixI 'True) (S1 ('MetaSel ('Just "lat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "lng") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) |
Address
Instances
Show Address Source # | |
Eq Address Source # | |
ToHttpApiData Address Source # | |
Defined in Web.Google.Maps.Common toUrlPiece :: Address -> Text # toEncodedUrlPiece :: Address -> Builder # toHeader :: Address -> ByteString # toQueryParam :: Address -> Text # |
Zoom level: the lowest level, in which the whole world can be seen, is 0. Each succeeding level doubles the precision. Not required if the map includes markers or paths.
Instances
Show Zoom Source # | |
Eq Zoom Source # | |
ToHttpApiData Zoom Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Zoom -> Text # toEncodedUrlPiece :: Zoom -> Builder # toHeader :: Zoom -> ByteString # toQueryParam :: Zoom -> Text # |
Size in pixels: there are maximum allowable values.
Instances
Show Size Source # | |
Eq Size Source # | |
ToHttpApiData Size Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Size -> Text # toEncodedUrlPiece :: Size -> Builder # toHeader :: Size -> ByteString # toQueryParam :: Size -> Text # |
Scale
Instances
Show Scale Source # | |
Eq Scale Source # | |
ToHttpApiData Scale Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Scale -> Text # toEncodedUrlPiece :: Scale -> Builder # toHeader :: Scale -> ByteString # toQueryParam :: Scale -> Text # |
Image format
Instances
Show Format Source # | |
Eq Format Source # | |
ToHttpApiData Format Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Format -> Text # toEncodedUrlPiece :: Format -> Builder # toHeader :: Format -> ByteString # toQueryParam :: Format -> Text # |
MapStyle
Instances
Show MapStyle Source # | |
Eq MapStyle Source # | |
ToHttpApiData MapStyle Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: MapStyle -> Text # toEncodedUrlPiece :: MapStyle -> Builder # toHeader :: MapStyle -> ByteString # toQueryParam :: MapStyle -> Text # |
Map feature
Instances
Show Feature Source # | |
Eq Feature Source # | |
ToHttpApiData Feature Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Feature -> Text # toEncodedUrlPiece :: Feature -> Builder # toHeader :: Feature -> ByteString # toQueryParam :: Feature -> Text # |
Feature element
AllElements | |
AllGeometry | |
GeometryFill | |
GeometryStroke | |
AllLabels | |
LabelsIcon | |
LabelsText | |
LabelsTextFill | |
LabelsTextStroke |
Instances
Show Element Source # | |
Eq Element Source # | |
ToHttpApiData Element Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Element -> Text # toEncodedUrlPiece :: Element -> Builder # toHeader :: Element -> ByteString # toQueryParam :: Element -> Text # |
data MapStyleOp Source #
Map style operation
StyleHue Word8 Word8 Word8 | |
StyleLightness Double | |
StyleSaturation Double | |
StyleGamma Double | |
StyleInvertLightness Bool | |
StyleVisibility Visibility | |
StyleColor Word8 Word8 Word8 | |
StyleWeight Int |
Instances
Show MapStyleOp Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> MapStyleOp -> ShowS # show :: MapStyleOp -> String # showList :: [MapStyleOp] -> ShowS # | |
Eq MapStyleOp Source # | |
Defined in Web.Google.Maps.Static (==) :: MapStyleOp -> MapStyleOp -> Bool # (/=) :: MapStyleOp -> MapStyleOp -> Bool # | |
ToHttpApiData MapStyleOp Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: MapStyleOp -> Text # toEncodedUrlPiece :: MapStyleOp -> Builder # toHeader :: MapStyleOp -> ByteString # toQueryParam :: MapStyleOp -> Text # | |
ToHttpApiData [MapStyleOp] Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: [MapStyleOp] -> Text # toEncodedUrlPiece :: [MapStyleOp] -> Builder # toHeader :: [MapStyleOp] -> ByteString # toQueryParam :: [MapStyleOp] -> Text # |
data Visibility Source #
Visibility
On | |
Off | |
Simplified | Removes some, not all, style features |
Instances
Show Visibility Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> Visibility -> ShowS # show :: Visibility -> String # showList :: [Visibility] -> ShowS # | |
Eq Visibility Source # | |
Defined in Web.Google.Maps.Static (==) :: Visibility -> Visibility -> Bool # (/=) :: Visibility -> Visibility -> Bool # | |
ToHttpApiData Visibility Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Visibility -> Text # toEncodedUrlPiece :: Visibility -> Builder # toHeader :: Visibility -> ByteString # toQueryParam :: Visibility -> Text # |
Map type
Instances
Show MapType Source # | |
Eq MapType Source # | |
ToHttpApiData MapType Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: MapType -> Text # toEncodedUrlPiece :: MapType -> Builder # toHeader :: MapType -> ByteString # toQueryParam :: MapType -> Text # |
Language: supported languages based on the list at https://developers.google.com/maps/faq#languagesupport (as at 20 March 2022).
Instances
Show Language Source # | |
Eq Language Source # | |
ToHttpApiData Language Source # | |
Defined in Web.Google.Maps.Common toUrlPiece :: Language -> Text # toEncodedUrlPiece :: Language -> Builder # toHeader :: Language -> ByteString # toQueryParam :: Language -> Text # |
Region: a ccTLD (country code top level domain).
AD | |
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 | |
UK | |
EU |
Instances
Show Region Source # | |
Eq Region Source # | |
ToHttpApiData Region Source # | |
Defined in Web.Google.Maps.Common toUrlPiece :: Region -> Text # toEncodedUrlPiece :: Region -> Builder # toHeader :: Region -> ByteString # toQueryParam :: Region -> Text # |
Markers
Instances
Show Markers Source # | |
Eq Markers Source # | |
ToHttpApiData Markers Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Markers -> Text # toEncodedUrlPiece :: Markers -> Builder # toHeader :: Markers -> ByteString # toQueryParam :: Markers -> Text # |
data MarkerStyle Source #
Marker style
Instances
Show MarkerStyle Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> MarkerStyle -> ShowS # show :: MarkerStyle -> String # showList :: [MarkerStyle] -> ShowS # | |
Eq MarkerStyle Source # | |
Defined in Web.Google.Maps.Static (==) :: MarkerStyle -> MarkerStyle -> Bool # (/=) :: MarkerStyle -> MarkerStyle -> Bool # | |
ToHttpApiData MarkerStyle Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: MarkerStyle -> Text # toEncodedUrlPiece :: MarkerStyle -> Builder # toHeader :: MarkerStyle -> ByteString # toQueryParam :: MarkerStyle -> Text # |
data MarkerSize Source #
Marker size
Instances
Show MarkerSize Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> MarkerSize -> ShowS # show :: MarkerSize -> String # showList :: [MarkerSize] -> ShowS # | |
Eq MarkerSize Source # | |
Defined in Web.Google.Maps.Static (==) :: MarkerSize -> MarkerSize -> Bool # (/=) :: MarkerSize -> MarkerSize -> Bool # | |
ToHttpApiData MarkerSize Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: MarkerSize -> Text # toEncodedUrlPiece :: MarkerSize -> Builder # toHeader :: MarkerSize -> ByteString # toQueryParam :: MarkerSize -> Text # |
data MarkerColor Source #
Marker colour
Instances
Show MarkerColor Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> MarkerColor -> ShowS # show :: MarkerColor -> String # showList :: [MarkerColor] -> ShowS # | |
Eq MarkerColor Source # | |
Defined in Web.Google.Maps.Static (==) :: MarkerColor -> MarkerColor -> Bool # (/=) :: MarkerColor -> MarkerColor -> Bool # | |
ToHttpApiData MarkerColor Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: MarkerColor -> Text # toEncodedUrlPiece :: MarkerColor -> Builder # toHeader :: MarkerColor -> ByteString # toQueryParam :: MarkerColor -> Text # |
newtype MarkerLabel Source #
Marker label character
Instances
Show MarkerLabel Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> MarkerLabel -> ShowS # show :: MarkerLabel -> String # showList :: [MarkerLabel] -> ShowS # | |
Eq MarkerLabel Source # | |
Defined in Web.Google.Maps.Static (==) :: MarkerLabel -> MarkerLabel -> Bool # (/=) :: MarkerLabel -> MarkerLabel -> Bool # | |
ToHttpApiData MarkerLabel Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: MarkerLabel -> Text # toEncodedUrlPiece :: MarkerLabel -> Builder # toHeader :: MarkerLabel -> ByteString # toQueryParam :: MarkerLabel -> Text # |
Standard colours
Instances
Show StdColor Source # | |
Eq StdColor Source # | |
ToHttpApiData StdColor Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: StdColor -> Text # toEncodedUrlPiece :: StdColor -> Builder # toHeader :: StdColor -> ByteString # toQueryParam :: StdColor -> Text # |
Represents a general universal resource identifier using its component parts.
For example, for the URI
foo://anonymous@www.haskell.org:42/ghc?query#frag
the components are:
Instances
Data URI | |
Defined in Network.URI gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URI -> c URI # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URI # dataTypeOf :: URI -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URI) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URI) # gmapT :: (forall b. Data b => b -> b) -> URI -> URI # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQ :: (forall d. Data d => d -> u) -> URI -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URI -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # | |
Generic URI | |
Show URI | |
NFData URI | |
Defined in Network.URI | |
Eq URI | |
Ord URI | |
Lift URI | |
type Rep URI | |
Defined in Network.URI type Rep URI = D1 ('MetaData "URI" "Network.URI" "network-uri-2.6.4.2-HOWkOsJ6iQ9LdZ2sAMVHdr" 'False) (C1 ('MetaCons "URI" 'PrefixI 'True) ((S1 ('MetaSel ('Just "uriScheme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriAuthority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe URIAuth))) :*: (S1 ('MetaSel ('Just "uriPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "uriQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriFragment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) |
Type for authority value within a URI
URIAuth | |
|
Instances
Data URIAuth | |
Defined in Network.URI gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URIAuth -> c URIAuth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URIAuth # toConstr :: URIAuth -> Constr # dataTypeOf :: URIAuth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URIAuth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URIAuth) # gmapT :: (forall b. Data b => b -> b) -> URIAuth -> URIAuth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URIAuth -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URIAuth -> r # gmapQ :: (forall d. Data d => d -> u) -> URIAuth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URIAuth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth # | |
Generic URIAuth | |
Show URIAuth | |
NFData URIAuth | |
Defined in Network.URI | |
Eq URIAuth | |
Ord URIAuth | |
Lift URIAuth | |
type Rep URIAuth | |
Defined in Network.URI type Rep URIAuth = D1 ('MetaData "URIAuth" "Network.URI" "network-uri-2.6.4.2-HOWkOsJ6iQ9LdZ2sAMVHdr" 'False) (C1 ('MetaCons "URIAuth" 'PrefixI 'True) (S1 ('MetaSel ('Just "uriUserInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "uriRegName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
Anchor
Instances
Show Anchor Source # | |
Eq Anchor Source # | |
ToHttpApiData Anchor Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Anchor -> Text # toEncodedUrlPiece :: Anchor -> Builder # toHeader :: Anchor -> ByteString # toQueryParam :: Anchor -> Text # |
Standard anchor points
AnchorTop | |
AnchorBottom | |
AnchorLeft | |
AnchorRight | |
AnchorCenter | |
AnchorTopLeft | |
AnchorTopRight | |
AnchorBottomLeft | |
AnchorBottomRight |
Instances
Show StdAnchor Source # | |
Eq StdAnchor Source # | |
ToHttpApiData StdAnchor Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: StdAnchor -> Text # toEncodedUrlPiece :: StdAnchor -> Builder # toHeader :: StdAnchor -> ByteString # toQueryParam :: StdAnchor -> Text # |
Path
Instances
Show Path Source # | |
Eq Path Source # | |
ToHttpApiData Path Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Path -> Text # toEncodedUrlPiece :: Path -> Builder # toHeader :: Path -> ByteString # toQueryParam :: Path -> Text # |
Path style: a geodesic path follows the curvature of the Earth.
PathStyle | |
|
Instances
Show PathStyle Source # | |
Eq PathStyle Source # | |
ToHttpApiData PathStyle Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: PathStyle -> Text # toEncodedUrlPiece :: PathStyle -> Builder # toHeader :: PathStyle -> ByteString # toQueryParam :: PathStyle -> Text # |
newtype PathWeight Source #
Path weight: in pixels.
Instances
Show PathWeight Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> PathWeight -> ShowS # show :: PathWeight -> String # showList :: [PathWeight] -> ShowS # | |
Eq PathWeight Source # | |
Defined in Web.Google.Maps.Static (==) :: PathWeight -> PathWeight -> Bool # (/=) :: PathWeight -> PathWeight -> Bool # | |
ToHttpApiData PathWeight Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: PathWeight -> Text # toEncodedUrlPiece :: PathWeight -> Builder # toHeader :: PathWeight -> ByteString # toQueryParam :: PathWeight -> Text # |
Path colour
Instances
Show PathColor Source # | |
Eq PathColor Source # | |
ToHttpApiData PathColor Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: PathColor -> Text # toEncodedUrlPiece :: PathColor -> Builder # toHeader :: PathColor -> ByteString # toQueryParam :: PathColor -> Text # |
newtype PathGeodesic Source #
Path is geodesic
Instances
Show PathGeodesic Source # | |
Defined in Web.Google.Maps.Static showsPrec :: Int -> PathGeodesic -> ShowS # show :: PathGeodesic -> String # showList :: [PathGeodesic] -> ShowS # | |
Eq PathGeodesic Source # | |
Defined in Web.Google.Maps.Static (==) :: PathGeodesic -> PathGeodesic -> Bool # (/=) :: PathGeodesic -> PathGeodesic -> Bool # | |
ToHttpApiData PathGeodesic Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: PathGeodesic -> Text # toEncodedUrlPiece :: PathGeodesic -> Builder # toHeader :: PathGeodesic -> ByteString # toQueryParam :: PathGeodesic -> Text # |
Visible locations
Instances
Show Visible Source # | |
Eq Visible Source # | |
ToHttpApiData Visible Source # | |
Defined in Web.Google.Maps.Static toUrlPiece :: Visible -> Text # toEncodedUrlPiece :: Visible -> Builder # toHeader :: Visible -> ByteString # toQueryParam :: Visible -> Text # |
type StaticmapResponse = DynamicImage Source #
StaticmapResponse