ziptastic-client-0.3.0.1: A type-safe client for the Ziptastic API for doing forward and reverse geocoding.

Safe HaskellNone
LanguageHaskell2010

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)

Synopsis

Documentation

newtype ApiKey :: * #

Constructors

ApiKey 

Fields

Instances

Eq ApiKey 

Methods

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

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

Show ApiKey 
IsString ApiKey 

Methods

fromString :: String -> ApiKey #

Generic ApiKey 

Associated Types

type Rep ApiKey :: * -> * #

Methods

from :: ApiKey -> Rep ApiKey x #

to :: Rep ApiKey x -> ApiKey #

ToHttpApiData ApiKey 
type Rep ApiKey 
type Rep ApiKey = D1 (MetaData "ApiKey" "Ziptastic.Core" "ziptastic-core-0.2.0.1-uTSzfdGQhR97oRWrUTSCj" True) (C1 (MetaCons "ApiKey" PrefixI True) (S1 (MetaSel (Just Symbol "getApiKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data LocaleInfo :: * #

Constructors

LocaleInfo 

Fields

Instances

Eq LocaleInfo 
Show LocaleInfo 
Generic LocaleInfo 

Associated Types

type Rep LocaleInfo :: * -> * #

FromJSON LocaleInfo 
type Rep LocaleInfo 

data LocaleCoords :: * #

Constructors

LocaleCoords 

Fields

Instances

forwardGeocode Source #

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.

reverseGeocode Source #

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.