Copyright | (c) Mike Pilgrem 2017 |
---|---|
Maintainer | public@pilgrem.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Web.Google.Static.Maps
Description
This module has no connection with Google Inc. or its affiliates.
The Google Static Maps 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 Static Maps API services is subject to the Google Maps APIs Terms of Service, which terms restrict the use of content.
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 Static Maps 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.Static.Maps (Center (..), Key (..), Location (..), Size (..), staticmap, StaticmapResponse (..), Zoom (..)) main :: IO () main = do putStrLn "A test of the Google Static Maps API.\nNB: The use of the \ \API services is subject to the Google Maps APIs Terms of Serivce \ \at https://developers.google.com/maps/terms.\n" mgr <- newManager tlsManagerSettings let apiKey = Key "<REPLACE_THIS_WITH_YOUR_ACTUAL_GOOGLE_API_KEY>" secret = Just $ Secret "<REPLACE_THIS_WITH_YOUR_ACTUAL_GOOGLE_\ \URL_SIGNING_SECRET>" -- If using a digital signature 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 Static Maps API" window = InWindow title (w, h) (10, 10) display window white picture Left err -> putStrLn $ "Error! Result:\n" ++ show err
- 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 GoogleStaticMapsAPI = "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 GoogleStaticMapsAPI
- 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
- = Arabic
- | Basque
- | Bengali
- | Bulgarian
- | 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
- | Korean
- | Latvian
- | Lithuanian
- | Malayalam
- | Marathi
- | Norwegian
- | Polish
- | Portuguese
- | PortugueseBrazil
- | PortuguesePortugal
- | Romanian
- | Russian
- | Serbian
- | Slovak
- | Slovenian
- | Spanish
- | Swedish
- | Tagalog
- | Tamil
- | Telugu
- | Thai
- | Turkish
- | Ukrainian
- | 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 Static Maps API services is subject to the Google Maps APIs Terms of Service.
API
type GoogleStaticMapsAPI = "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 Static Maps API
api :: Proxy GoogleStaticMapsAPI Source #
API type
Types
API key
Secret for digital signature
Signature
Center of the map: not required if the map includes markers or paths.
Location
Latitude and longitude: precision beyond 6 decimal places is ignored.
Constructors
LatLng | |
Address
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.
Size in pixels: there are maximum allowable values.
Scale
Image format
MapStyle
Map feature
Constructors
Feature element
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
data Visibility Source #
Visibility
Constructors
On | |
Off | |
Simplified | Removes some, not all, style features |
Instances
Map type
Language: supported languages based on the list at https://developers.google.com/maps/faq#languagesupport (as at 13 March 2017).
Constructors
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 |
Markers
Constructors
Markers (Maybe MarkerStyle) [Location] |
data MarkerColor Source #
Marker colour
Constructors
MarkerColor Word8 Word8 Word8 | |
StdMarkerColor StdColor |
Instances
Standard colours
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 | |
Type for authority value within a URI
Constructors
URIAuth | |
Fields
|
Anchor
Constructors
AnchorPoint Int Int | |
StdAnchor StdAnchor |
Standard anchor points
Path
Path style: a geodesic path follows the curvature of the Earth.
Constructors
PathStyle | |
Fields
|
Path colour
Visible locations
type StaticmapResponse = DynamicImage Source #
StaticmapResponse