aboutsummaryrefslogtreecommitdiff
path: root/lib/Web/OpenWeatherMap
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Web/OpenWeatherMap')
-rw-r--r--lib/Web/OpenWeatherMap/API.hs44
-rw-r--r--lib/Web/OpenWeatherMap/Client.hs21
-rw-r--r--lib/Web/OpenWeatherMap/Types/Location.hs34
3 files changed, 47 insertions, 52 deletions
diff --git a/lib/Web/OpenWeatherMap/API.hs b/lib/Web/OpenWeatherMap/API.hs
index 516845c..8dde5c7 100644
--- a/lib/Web/OpenWeatherMap/API.hs
+++ b/lib/Web/OpenWeatherMap/API.hs
@@ -6,10 +6,8 @@ For API key (a.k.a appid) refer to <http://openweathermap.org/appid>.
{-# LANGUAGE TypeOperators #-}
module Web.OpenWeatherMap.API
- ( weatherByName
- , weatherByCoord
- , forecastByName
- , forecastByCoord
+ ( currentWeather
+ , forecastWeather
) where
import Data.Proxy (Proxy(..))
@@ -19,44 +17,18 @@ import Servant.Client (ClientM, client)
import Web.OpenWeatherMap.Types.CurrentWeather (CurrentWeather)
import Web.OpenWeatherMap.Types.ForecastWeather (ForecastWeather)
+import Web.OpenWeatherMap.Types.Location (Location)
type QueryParam = QueryParam' '[ Required, Strict]
-type GetCurrentWeather = AppId :> Get '[ JSON] CurrentWeather
-
-type GetForecastWeather = AppId :> Get '[ JSON] ForecastWeather
-
-type AppId = QueryParam "appid" String
-
type Current
- = "weather" :> (QueryParam "q" String :> GetCurrentWeather :<|> QueryParam "lat" Double :> QueryParam "lon" Double :> GetCurrentWeather)
+ = "weather" :> QueryParam "appid" String :> Location :> Get '[ JSON] CurrentWeather
type Forecast
- = "forecast" :> (QueryParam "q" String :> GetForecastWeather :<|> QueryParam "lat" Double :> QueryParam "lon" Double :> GetForecastWeather)
+ = "forecast" :> QueryParam "appid" String :> Location :> Get '[ JSON] ForecastWeather
type API = Current :<|> Forecast
--- | Request current weather in the city.
-weatherByName ::
- String -- ^ City name, e. g. \"Moscow\" or \"Moscow,ru\".
- -> String -- ^ API key.
- -> ClientM CurrentWeather
--- | Request current weather at the geographic coordinates (in decimal degrees).
-weatherByCoord ::
- Double -- ^ Latitude, e. g. 55.7522200 for Moscow.
- -> Double -- ^ Longitude, e. g. 37.6155600 for Moscow.
- -> String -- ^ API key.
- -> ClientM CurrentWeather
--- | Request forecast weather in the city.
-forecastByName ::
- String -- ^ City name, e. g. \"Moscow\" or \"Moscow,ru\".
- -> String -- ^ API key.
- -> ClientM ForecastWeather
--- | Request current weather at the geographic coordinates (in decimal degrees).
-forecastByCoord ::
- Double -- ^ Latitude, e. g. 55.7522200 for Moscow.
- -> Double -- ^ Longitude, e. g. 37.6155600 for Moscow.
- -> String -- ^ API key.
- -> ClientM ForecastWeather
-(weatherByName :<|> weatherByCoord) :<|> (forecastByName :<|> forecastByCoord) =
- client (Proxy :: Proxy API)
+forecastWeather :: String -> Location -> ClientM ForecastWeather
+currentWeather :: String -> Location -> ClientM CurrentWeather
+(currentWeather :<|> forecastWeather) = client (Proxy :: Proxy API)
diff --git a/lib/Web/OpenWeatherMap/Client.hs b/lib/Web/OpenWeatherMap/Client.hs
index d760812..31719bb 100644
--- a/lib/Web/OpenWeatherMap/Client.hs
+++ b/lib/Web/OpenWeatherMap/Client.hs
@@ -2,8 +2,7 @@
High-level client functions perfoming requests to OpenWeatherMap API.
-}
module Web.OpenWeatherMap.Client
- ( Location(..)
- , getWeather
+ ( getWeather
, getForecast
) where
@@ -20,12 +19,7 @@ import Servant.Client
import qualified Web.OpenWeatherMap.API as API
import Web.OpenWeatherMap.Types.CurrentWeather (CurrentWeather)
import Web.OpenWeatherMap.Types.ForecastWeather (ForecastWeather)
-
--- | Various way to specify location.
-data Location
- = Name String -- ^ City name.
- | Coord Double
- Double -- ^ Geographic coordinates: latitude and longitude.
+import Web.OpenWeatherMap.Types.Location (Location)
-- | Make a request to OpenWeatherMap API
-- and return current weather in given location.
@@ -33,10 +27,7 @@ getWeather ::
String -- ^ API key.
-> Location
-> IO (Either ClientError CurrentWeather)
-getWeather appid loc = defaultEnv >>= runClientM (api loc appid)
- where
- api (Name city) = API.weatherByName city
- api (Coord lat lon) = API.weatherByCoord lat lon
+getWeather appid loc = defaultEnv >>= runClientM (API.currentWeather appid loc)
-- | Make a request to OpenWeatherMap API
-- and return forecast weather in given location.
@@ -44,10 +35,8 @@ getForecast ::
String -- ^ API key.
-> Location
-> IO (Either ClientError ForecastWeather)
-getForecast appid loc = defaultEnv >>= runClientM (api loc appid)
- where
- api (Name city) = API.forecastByName city
- api (Coord lat lon) = API.forecastByCoord lat lon
+getForecast appid loc =
+ defaultEnv >>= runClientM (API.forecastWeather appid loc)
defaultEnv :: IO ClientEnv
defaultEnv = do
diff --git a/lib/Web/OpenWeatherMap/Types/Location.hs b/lib/Web/OpenWeatherMap/Types/Location.hs
new file mode 100644
index 0000000..72712ed
--- /dev/null
+++ b/lib/Web/OpenWeatherMap/Types/Location.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+
+module Web.OpenWeatherMap.Types.Location
+ ( Location(..)
+ ) where
+
+import Data.Proxy (Proxy(..))
+
+import Servant.API ((:>))
+import Servant.Client (Client, HasClient, clientWithRoute, hoistClientMonad)
+import Servant.Client.Core.Request (appendToQueryString)
+import Web.HttpApiData (toQueryParam)
+
+-- | Various way to specify location.
+data Location
+ = Name String -- ^ City name.
+ | Coord Double Double -- ^ Geographic coordinates: latitude and longitude.
+
+instance HasClient m api => HasClient m (Location :> api) where
+ type Client m (Location :> api) = Location -> Client m api
+ clientWithRoute pm Proxy req loc =
+ clientWithRoute pm (Proxy :: Proxy api) (addParams loc req)
+ where
+ addParams (Name q) = appendToQueryString "q" (Just $ toQueryParam q)
+ addParams (Coord lat lon) =
+ appendToQueryString "lat" (Just $ toQueryParam lat) .
+ appendToQueryString "lon" (Just $ toQueryParam lon)
+ hoistClientMonad pm _ f cl =
+ \a -> hoistClientMonad pm (Proxy :: Proxy api) f (cl a)