| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ziptastic.Client
Description
This module provides a simple interface to Ziptastic's forward and reverse geocoding API (https://www.getziptastic.com/).
{-# LANGUAGE OverloadedStrings #-}
import Data.ISO3166_CountryCodes (CountryCode(US))
import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Ziptastic.Client
apiKey :: ApiKey
apiKey = "abcdefghijklmnopqrstuvwxyz"
main :: IO ()
main = do
manager <- newManager tlsManagerSettings
print =<< forwardGeocode apiKey manager US "48867"
print =<< reverseGeocode apiKey manager 42.9934 (-84.1595)- newtype ApiKey :: * = ApiKey {}
- data LocaleInfo :: * = LocaleInfo {}
- data LocaleCoords :: * = LocaleCoords {}
- forwardGeocode :: ApiKey -> Manager -> CountryCode -> Text -> IO (Either ServantError [LocaleInfo])
- reverseGeocode :: ApiKey -> Manager -> Double -> Double -> IO (Either ServantError [LocaleInfo])
- reverseGeocodeWithRadius :: ApiKey -> Manager -> Double -> Double -> Int -> IO (Either ServantError [LocaleInfo])
Documentation
data LocaleInfo :: * #
Constructors
| LocaleInfo | |
Fields
| |
Instances
data LocaleCoords :: * #
Constructors
| LocaleCoords | |
Fields
| |
Instances
Arguments
| :: ApiKey | |
| -> Manager | HTTP connection manager (if TLS is supported, request will be made over HTTPS) |
| -> CountryCode | country |
| -> Text | postal code |
| -> IO (Either ServantError [LocaleInfo]) |
Performs a forward geocode lookup at the given country and postal code.
The success result is a list because in rare cases you may receive multiple records.
If the request fails the result will be Left with an error.
Arguments
| :: ApiKey | |
| -> Manager | HTTP connection manager (if TLS is supported, request will be made over HTTPS) |
| -> Double | latitude |
| -> Double | longitude |
| -> IO (Either ServantError [LocaleInfo]) |
Performs a reverse geocode lookup at the given coordinates using a default radius of 5000 meters.
The success result is a list because in rare cases you may receive multiple records.
If the request fails the result will be Left with an error.
reverseGeocodeWithRadius Source #
Arguments
| :: ApiKey | |
| -> Manager | HTTP connection manager (if TLS is supported, request will be made over HTTPS) |
| -> Double | latitude |
| -> Double | longitude |
| -> Int | radius (in meters) |
| -> IO (Either ServantError [LocaleInfo]) |
Performs a reverse geocode lookup at the given coordinates using a specified radius in meters.
The success result is a list because in rare cases you may receive multiple records.
If the request fails the result will be Left with an error.