| Copyright | (c) Mike Pilgrem 2017 2018 |
|---|---|
| Maintainer | public@pilgrem.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.Google.Maps.Static
Description
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 errSynopsis
- 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 ServantError 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
- = Albanian
- | Arabic
- | Basque
- | Belarusian
- | Bengali
- | Bulgarian
- | Burmese
- | Catalan
- | ChineseSimplified
- | ChineseTraditional
- | Croatian
- | Czech
- | Danish
- | Dutch
- | German
- | Greek
- | English
- | EnglishAustralian
- | EnglishBritish
- | Farsi
- | Filipino
- | Finnish
- | French
- | Galician
- | Gujarati
- | Hebrew
- | Hindi
- | Hungarian
- | Indonesian
- | Italian
- | Japanese
- | Kannada
- | Kazakh
- | Korean
- | Kyrgyz
- | Latvian
- | Lithuanian
- | Macedonian
- | Malayalam
- | Marathi
- | Norwegian
- | Polish
- | Portuguese
- | PortugueseBrazil
- | PortuguesePortugal
- | Punjabi
- | Romanian
- | Russian
- | Serbian
- | Slovak
- | Slovenian
- | Spanish
- | Swedish
- | Tagalog
- | Tamil
- | Telugu
- | Thai
- | Turkish
- | Ukrainian
- | Uzbek
- | Vietnamese
- 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 ServantError 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
| Eq Key Source # | |
| Show Key Source # | |
| ToHttpApiData Key Source # | |
Defined in Web.Google.Maps.Common Methods toUrlPiece :: Key -> Text # toEncodedUrlPiece :: Key -> Builder # toHeader :: Key -> ByteString # toQueryParam :: Key -> Text # | |
Secret for digital signature
Signature
Instances
| Eq Signature Source # | |
| Show Signature Source # | |
| ToHttpApiData Signature Source # | |
Defined in Web.Google.Maps.Static Methods 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
| Eq Center Source # | |
| Show Center Source # | |
| ToHttpApiData Center Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Center -> Text # toEncodedUrlPiece :: Center -> Builder # toHeader :: Center -> ByteString # toQueryParam :: Center -> Text # | |
Location
Instances
| Eq Location Source # | |
| Show Location Source # | |
| ToHttpApiData Location Source # | |
Defined in Web.Google.Maps.Common Methods toUrlPiece :: Location -> Text # toEncodedUrlPiece :: Location -> Builder # toHeader :: Location -> ByteString # toQueryParam :: Location -> Text # | |
| ToHttpApiData [Location] Source # | |
Defined in Web.Google.Maps.Common Methods toUrlPiece :: [Location] -> Text # toEncodedUrlPiece :: [Location] -> Builder # toHeader :: [Location] -> ByteString # toQueryParam :: [Location] -> Text # | |
Latitude and longitude: precision beyond 6 decimal places is ignored.
Constructors
| LatLng | |
Instances
| Eq LatLng Source # | |
| Show LatLng Source # | |
| Generic LatLng Source # | |
| FromJSON LatLng Source # | |
| ToHttpApiData LatLng Source # | |
Defined in Web.Google.Maps.Common Methods 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.6.0.0-3UHKR7MvECnDaEj7pHDv34" 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
| Eq Address Source # | |
| Show Address Source # | |
| ToHttpApiData Address Source # | |
Defined in Web.Google.Maps.Common Methods 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
| Eq Zoom Source # | |
| Show Zoom Source # | |
| ToHttpApiData Zoom Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Zoom -> Text # toEncodedUrlPiece :: Zoom -> Builder # toHeader :: Zoom -> ByteString # toQueryParam :: Zoom -> Text # | |
Size in pixels: there are maximum allowable values.
Instances
| Eq Size Source # | |
| Show Size Source # | |
| ToHttpApiData Size Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Size -> Text # toEncodedUrlPiece :: Size -> Builder # toHeader :: Size -> ByteString # toQueryParam :: Size -> Text # | |
Scale
Instances
| Eq Scale Source # | |
| Show Scale Source # | |
| ToHttpApiData Scale Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Scale -> Text # toEncodedUrlPiece :: Scale -> Builder # toHeader :: Scale -> ByteString # toQueryParam :: Scale -> Text # | |
Image format
Instances
| Eq Format Source # | |
| Show Format Source # | |
| ToHttpApiData Format Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Format -> Text # toEncodedUrlPiece :: Format -> Builder # toHeader :: Format -> ByteString # toQueryParam :: Format -> Text # | |
MapStyle
Instances
| Eq MapStyle Source # | |
| Show MapStyle Source # | |
| ToHttpApiData MapStyle Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: MapStyle -> Text # toEncodedUrlPiece :: MapStyle -> Builder # toHeader :: MapStyle -> ByteString # toQueryParam :: MapStyle -> Text # | |
Map feature
Constructors
Instances
| Eq Feature Source # | |
| Show Feature Source # | |
| ToHttpApiData Feature Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Feature -> Text # toEncodedUrlPiece :: Feature -> Builder # toHeader :: Feature -> ByteString # toQueryParam :: Feature -> Text # | |
Feature element
Constructors
| AllElements | |
| AllGeometry | |
| GeometryFill | |
| GeometryStroke | |
| AllLabels | |
| LabelsIcon | |
| LabelsText | |
| LabelsTextFill | |
| LabelsTextStroke |
Instances
| Eq Element Source # | |
| Show Element Source # | |
| ToHttpApiData Element Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Element -> Text # toEncodedUrlPiece :: Element -> Builder # toHeader :: Element -> ByteString # toQueryParam :: Element -> Text # | |
data MapStyleOp Source #
Map style operation
Constructors
| StyleHue Word8 Word8 Word8 | |
| StyleLightness Double | |
| StyleSaturation Double | |
| StyleGamma Double | |
| StyleInvertLightness Bool | |
| StyleVisibility Visibility | |
| StyleColor Word8 Word8 Word8 | |
| StyleWeight Int |
Instances
| Eq MapStyleOp Source # | |
Defined in Web.Google.Maps.Static | |
| Show MapStyleOp Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> MapStyleOp -> ShowS # show :: MapStyleOp -> String # showList :: [MapStyleOp] -> ShowS # | |
| ToHttpApiData MapStyleOp Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: MapStyleOp -> Text # toEncodedUrlPiece :: MapStyleOp -> Builder # toHeader :: MapStyleOp -> ByteString # toQueryParam :: MapStyleOp -> Text # | |
| ToHttpApiData [MapStyleOp] Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: [MapStyleOp] -> Text # toEncodedUrlPiece :: [MapStyleOp] -> Builder # toHeader :: [MapStyleOp] -> ByteString # toQueryParam :: [MapStyleOp] -> Text # | |
data Visibility Source #
Visibility
Constructors
| On | |
| Off | |
| Simplified | Removes some, not all, style features |
Instances
| Eq Visibility Source # | |
Defined in Web.Google.Maps.Static | |
| Show Visibility Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> Visibility -> ShowS # show :: Visibility -> String # showList :: [Visibility] -> ShowS # | |
| ToHttpApiData Visibility Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Visibility -> Text # toEncodedUrlPiece :: Visibility -> Builder # toHeader :: Visibility -> ByteString # toQueryParam :: Visibility -> Text # | |
Map type
Instances
| Eq MapType Source # | |
| Show MapType Source # | |
| ToHttpApiData MapType Source # | |
Defined in Web.Google.Maps.Static Methods 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 29 December 2018).
Constructors
Instances
| Eq Language Source # | |
| Show Language Source # | |
| ToHttpApiData Language Source # | |
Defined in Web.Google.Maps.Common Methods toUrlPiece :: Language -> Text # toEncodedUrlPiece :: Language -> Builder # toHeader :: Language -> ByteString # toQueryParam :: Language -> Text # | |
Region: a ccTLD (country code top level domain).
Constructors
| 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
| Eq Region Source # | |
| Show Region Source # | |
| ToHttpApiData Region Source # | |
Defined in Web.Google.Maps.Common Methods toUrlPiece :: Region -> Text # toEncodedUrlPiece :: Region -> Builder # toHeader :: Region -> ByteString # toQueryParam :: Region -> Text # | |
Markers
Constructors
| Markers (Maybe MarkerStyle) [Location] |
Instances
| Eq Markers Source # | |
| Show Markers Source # | |
| ToHttpApiData Markers Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Markers -> Text # toEncodedUrlPiece :: Markers -> Builder # toHeader :: Markers -> ByteString # toQueryParam :: Markers -> Text # | |
data MarkerStyle Source #
Marker style
Constructors
| StdMarkerStyle | |
Fields | |
| CustomIcon | |
Instances
| Eq MarkerStyle Source # | |
Defined in Web.Google.Maps.Static | |
| Show MarkerStyle Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> MarkerStyle -> ShowS # show :: MarkerStyle -> String # showList :: [MarkerStyle] -> ShowS # | |
| ToHttpApiData MarkerStyle Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: MarkerStyle -> Text # toEncodedUrlPiece :: MarkerStyle -> Builder # toHeader :: MarkerStyle -> ByteString # toQueryParam :: MarkerStyle -> Text # | |
data MarkerSize Source #
Marker size
Instances
| Eq MarkerSize Source # | |
Defined in Web.Google.Maps.Static | |
| Show MarkerSize Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> MarkerSize -> ShowS # show :: MarkerSize -> String # showList :: [MarkerSize] -> ShowS # | |
| ToHttpApiData MarkerSize Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: MarkerSize -> Text # toEncodedUrlPiece :: MarkerSize -> Builder # toHeader :: MarkerSize -> ByteString # toQueryParam :: MarkerSize -> Text # | |
data MarkerColor Source #
Marker colour
Constructors
| MarkerColor Word8 Word8 Word8 | |
| StdMarkerColor StdColor |
Instances
| Eq MarkerColor Source # | |
Defined in Web.Google.Maps.Static | |
| Show MarkerColor Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> MarkerColor -> ShowS # show :: MarkerColor -> String # showList :: [MarkerColor] -> ShowS # | |
| ToHttpApiData MarkerColor Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: MarkerColor -> Text # toEncodedUrlPiece :: MarkerColor -> Builder # toHeader :: MarkerColor -> ByteString # toQueryParam :: MarkerColor -> Text # | |
newtype MarkerLabel Source #
Marker label character
Constructors
| MarkerLabel Char |
Instances
| Eq MarkerLabel Source # | |
Defined in Web.Google.Maps.Static | |
| Show MarkerLabel Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> MarkerLabel -> ShowS # show :: MarkerLabel -> String # showList :: [MarkerLabel] -> ShowS # | |
| ToHttpApiData MarkerLabel Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: MarkerLabel -> Text # toEncodedUrlPiece :: MarkerLabel -> Builder # toHeader :: MarkerLabel -> ByteString # toQueryParam :: MarkerLabel -> Text # | |
Standard colours
Instances
| Eq StdColor Source # | |
| Show StdColor Source # | |
| ToHttpApiData StdColor Source # | |
Defined in Web.Google.Maps.Static Methods 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:
Constructors
| URI | |
Instances
| Eq URI | |
| Data URI | |
Defined in Network.URI Methods 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 :: (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 # | |
| Ord URI | |
| Show URI | |
| Generic URI | |
| NFData URI | |
Defined in Network.URI | |
| type Rep URI | |
Defined in Network.URI type Rep URI = D1 (MetaData "URI" "Network.URI" "network-uri-2.6.1.0-K75fCYvLQE41EntOQ30cqK" 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
Constructors
| URIAuth | |
Fields
| |
Instances
| Eq URIAuth | |
| Data URIAuth | |
Defined in Network.URI Methods 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 :: (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 # | |
| Ord URIAuth | |
| Show URIAuth | |
| NFData URIAuth | |
Defined in Network.URI | |
Anchor
Constructors
| AnchorPoint Int Int | |
| StdAnchor StdAnchor |
Instances
| Eq Anchor Source # | |
| Show Anchor Source # | |
| ToHttpApiData Anchor Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Anchor -> Text # toEncodedUrlPiece :: Anchor -> Builder # toHeader :: Anchor -> ByteString # toQueryParam :: Anchor -> Text # | |
Standard anchor points
Constructors
| AnchorTop | |
| AnchorBottom | |
| AnchorLeft | |
| AnchorRight | |
| AnchorCenter | |
| AnchorTopLeft | |
| AnchorTopRight | |
| AnchorBottomLeft | |
| AnchorBottomRight |
Instances
| Eq StdAnchor Source # | |
| Show StdAnchor Source # | |
| ToHttpApiData StdAnchor Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: StdAnchor -> Text # toEncodedUrlPiece :: StdAnchor -> Builder # toHeader :: StdAnchor -> ByteString # toQueryParam :: StdAnchor -> Text # | |
Path
Instances
| Eq Path Source # | |
| Show Path Source # | |
| ToHttpApiData Path Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Path -> Text # toEncodedUrlPiece :: Path -> Builder # toHeader :: Path -> ByteString # toQueryParam :: Path -> Text # | |
Path style: a geodesic path follows the curvature of the Earth.
Constructors
| PathStyle | |
Fields
| |
Instances
| Eq PathStyle Source # | |
| Show PathStyle Source # | |
| ToHttpApiData PathStyle Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: PathStyle -> Text # toEncodedUrlPiece :: PathStyle -> Builder # toHeader :: PathStyle -> ByteString # toQueryParam :: PathStyle -> Text # | |
newtype PathWeight Source #
Path weight: in pixels.
Constructors
| PathWeight Int |
Instances
| Eq PathWeight Source # | |
Defined in Web.Google.Maps.Static | |
| Show PathWeight Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> PathWeight -> ShowS # show :: PathWeight -> String # showList :: [PathWeight] -> ShowS # | |
| ToHttpApiData PathWeight Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: PathWeight -> Text # toEncodedUrlPiece :: PathWeight -> Builder # toHeader :: PathWeight -> ByteString # toQueryParam :: PathWeight -> Text # | |
Path colour
Constructors
| PathColor Word8 Word8 Word8 | |
| PathColorAlpha Word8 Word8 Word8 Word8 | |
| StdPathColor StdColor |
Instances
| Eq PathColor Source # | |
| Show PathColor Source # | |
| ToHttpApiData PathColor Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: PathColor -> Text # toEncodedUrlPiece :: PathColor -> Builder # toHeader :: PathColor -> ByteString # toQueryParam :: PathColor -> Text # | |
newtype PathGeodesic Source #
Path is geodesic
Constructors
| PathGeodesic Bool |
Instances
| Eq PathGeodesic Source # | |
Defined in Web.Google.Maps.Static | |
| Show PathGeodesic Source # | |
Defined in Web.Google.Maps.Static Methods showsPrec :: Int -> PathGeodesic -> ShowS # show :: PathGeodesic -> String # showList :: [PathGeodesic] -> ShowS # | |
| ToHttpApiData PathGeodesic Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: PathGeodesic -> Text # toEncodedUrlPiece :: PathGeodesic -> Builder # toHeader :: PathGeodesic -> ByteString # toQueryParam :: PathGeodesic -> Text # | |
Visible locations
Instances
| Eq Visible Source # | |
| Show Visible Source # | |
| ToHttpApiData Visible Source # | |
Defined in Web.Google.Maps.Static Methods toUrlPiece :: Visible -> Text # toEncodedUrlPiece :: Visible -> Builder # toHeader :: Visible -> ByteString # toQueryParam :: Visible -> Text # | |
type StaticmapResponse = DynamicImage Source #
StaticmapResponse