aboutsummaryrefslogtreecommitdiff
path: root/lib/Web/OpenWeatherMap/Types/Location.hs
diff options
context:
space:
mode:
authorIgor Pashev <pashev.igor@gmail.com>2020-06-28 17:36:49 +0200
committerIgor Pashev <pashev.igor@gmail.com>2020-06-28 17:36:49 +0200
commit27b29703a46bcde319961c2b52d38da3513a1da8 (patch)
tree474c50433763dd491e4ab213c24072f6f06ecc1d /lib/Web/OpenWeatherMap/Types/Location.hs
parente7a5255ed66162cebea785af30d3b534649ab24b (diff)
downloadopenweathermap-27b29703a46bcde319961c2b52d38da3513a1da8.tar.gz
Make location a part of API
Diffstat (limited to 'lib/Web/OpenWeatherMap/Types/Location.hs')
-rw-r--r--lib/Web/OpenWeatherMap/Types/Location.hs34
1 files changed, 34 insertions, 0 deletions
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)