aboutsummaryrefslogtreecommitdiff
path: root/lib/Web/OpenWeatherMap/Types/Location.hs
blob: 85b4ca65d188593d5142b0b12d3bc9c5910e4fff (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
{-# 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 ways 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 = hoistClientMonad pm (Proxy :: Proxy api) f . cl