google-maps-geocoding-0.1.0.0: Google Maps Geocoding API bindings

Copyright(c) Mike Pilgrem 2017
Maintainerpublic@pilgrem.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Web.Google.Maps.Geocoding

Contents

Description

The Google Maps Geocoding API provides a direct way to access geocoding and reverse geocoding services via an HTTP request.

The components and optional parameters in a geocoding request are not yet implemented. The reverse geocoding request is not yet implemented.

Below is an example of use.

{-# LANGUAGE OverloadedStrings #-}

module Main (main) where

import Data.Text (Text)
import Data.Text.IO as T (getLine, putStr)
import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Web.Google.Maps.Geocoding (Address (..), geocode, GeocodingResponse (..),
    Geometry (..), Key (..), Location (..), Result (..), Status (..))
import System.IO (hFlush, stdout)

main :: IO ()
main = do
    txt <- input "Enter full address: "
    mgr <- newManager tlsManagerSettings
    let apiKey = Key "<GOOGLE_API_KEY>"
    result <- geocode mgr apiKey (Address txt)
    case result of
        Right response -> do
            let s = status response
            case s of
               OK -> print $ location $ geometry $ head $ results response
                _  -> putStrLn $ "Error! Status: " ++ show s
        _ -> putStrLn $ "Error! Result:\n" ++ show result

input :: Text -> IO Text
input msg = T.putStr msg >> hFlush stdout >> T.getLine

Synopsis

Functions

API

type GoogleMapsGeocodingAPI = "json" :> (QueryParam "key" Key :> (QueryParam "address" Address :> Get '[JSON] GeocodingResponse)) Source #

Google Translate API

Types

newtype Key Source #

API key

Constructors

Key Text 

Instances

data Status Source #

Contains the status of the request and may contain debugging information to help you track down why geocoding is not working.

Constructors

OK

Indicates that no errors occurred; the address was successfully parsed and at least one geocode was returned.

ZeroResults

Indicates that the geocode was successful but returned no results. This may occur if the geocoder was passed a non-existent address.

OverQueryLimit 
RequestDenied 
InvalidRequest

Generally indicates that the query (address, components or latlng) is missing.

UnknownError 

data Result Source #

A result of the geocoder.

Instances

Eq Result Source # 

Methods

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

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

Show Result Source # 
Generic Result Source # 

Associated Types

type Rep Result :: * -> * #

Methods

from :: Result -> Rep Result x #

to :: Rep Result x -> Result #

FromJSON Result Source # 
type Rep Result Source # 

data AddressType Source #

Address (and address component) type: The list of types provided by Google (as at 4 March 2017) is incomplete.

Constructors

AddressType Text 

Instances

newtype PostcodeLocality Source #

Postcode locality: a locality contained in a postal code

Constructors

PostcodeLocality Text 

newtype PlaceId Source #

Place id

Constructors

PlaceId Text 

Instances

Eq PlaceId Source # 

Methods

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

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

Show PlaceId Source # 
Generic PlaceId Source # 

Associated Types

type Rep PlaceId :: * -> * #

Methods

from :: PlaceId -> Rep PlaceId x #

to :: Rep PlaceId x -> PlaceId #

FromJSON PlaceId Source # 
type Rep PlaceId Source # 
type Rep PlaceId = D1 (MetaData "PlaceId" "Web.Google.Maps.Geocoding" "google-maps-geocoding-0.1.0.0-3L33WkwMNtIIeZ1iEWZa3x" True) (C1 (MetaCons "PlaceId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Location Source #

Location

Constructors

Location 

Fields

Instances

Eq Location Source # 
Show Location Source # 
Generic Location Source # 

Associated Types

type Rep Location :: * -> * #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

FromJSON Location Source # 
type Rep Location Source # 
type Rep Location = D1 (MetaData "Location" "Web.Google.Maps.Geocoding" "google-maps-geocoding-0.1.0.0-3L33WkwMNtIIeZ1iEWZa3x" False) (C1 (MetaCons "Location" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "lat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) (S1 (MetaSel (Just Symbol "lng") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))))

data Viewport Source #

Viewport

Constructors

Viewport 

Instances

Eq Viewport Source # 
Show Viewport Source # 
Generic Viewport Source # 

Associated Types

type Rep Viewport :: * -> * #

Methods

from :: Viewport -> Rep Viewport x #

to :: Rep Viewport x -> Viewport #

FromJSON Viewport Source # 
type Rep Viewport Source # 
type Rep Viewport = D1 (MetaData "Viewport" "Web.Google.Maps.Geocoding" "google-maps-geocoding-0.1.0.0-3L33WkwMNtIIeZ1iEWZa3x" False) (C1 (MetaCons "Viewport" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "southwest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Location)) (S1 (MetaSel (Just Symbol "northeast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Location))))