module Ziptastic.Client
( ApiKey(..)
, LocaleInfo(..)
, Core.LocaleCoords(..)
, forwardGeocode
, reverseGeocode
, reverseGeocodeWithRadius
) where
import Data.ISO3166_CountryCodes (CountryCode)
import Data.Proxy (Proxy(..))
import Data.Text (Text)
import Network.HTTP.Client (Manager)
import Servant.API ((:<|>)(..))
import Servant.Client
( BaseUrl(..), ClientEnv(..), ClientM, Scheme(..), ServantError
, client, runClientM
)
import Ziptastic.Core (ApiKey, ForApi(..), LocaleInfo)
import qualified Ziptastic.Core as Core
forwardGeocode :: ApiKey
-> Manager
-> CountryCode
-> Text
-> IO (Either ServantError [LocaleInfo])
forwardGeocode apiKey manager countryCode postalCode = runClientM func (ClientEnv manager baseUrl)
where func = forwardGeocode' (apiClient apiKey) (ForApi countryCode) postalCode
reverseGeocode :: ApiKey
-> Manager
-> Double
-> Double
-> IO (Either ServantError [LocaleInfo])
reverseGeocode apiKey manager lat long = reverseGeocodeWithRadius apiKey manager lat long 5000
reverseGeocodeWithRadius :: ApiKey
-> Manager
-> Double
-> Double
-> Int
-> IO (Either ServantError [LocaleInfo])
reverseGeocodeWithRadius apiKey manager lat long radius = runClientM func (ClientEnv manager baseUrl)
where func = reverseGeocodeWithRadius' (mkReverseGeocode (apiClient apiKey) lat long) radius
data ApiClient = ApiClient
{ forwardGeocode' :: ForApi CountryCode -> Text -> ClientM [LocaleInfo]
, mkReverseGeocode :: Double -> Double -> ReverseGeocodeApiClient
}
data ReverseGeocodeApiClient = ReverseGeocodeApiClient
{ reverseGeocodeWithRadius' :: Int -> ClientM [LocaleInfo]
, reverseGeocode' :: ClientM [LocaleInfo]
}
apiClient :: ApiKey -> ApiClient
apiClient apiKey = ApiClient
{ forwardGeocode' = forwardGeocodeApi
, mkReverseGeocode = mkReversGeocodeEndpoints
}
where
forwardGeocodeApi :<|> reverseGeocodeApi = client (Proxy :: Proxy Core.Api) (Just apiKey)
mkReversGeocodeEndpoints lat long = ReverseGeocodeApiClient
{ reverseGeocodeWithRadius' = withRadius
, reverseGeocode' = withDefaultRadius
}
where
withRadius :<|> withDefaultRadius = reverseGeocodeApi lat long
baseUrl :: BaseUrl
baseUrl = BaseUrl
{ baseUrlScheme = if Core.baseUrlIsHttps then Https else Http
, baseUrlHost = Core.baseUrlHost
, baseUrlPort = Core.baseUrlPort
, baseUrlPath = Core.baseUrlPath
}