-- | Helpers for dealing with HTTP requests.
module Strive.Internal.HTTP
  ( delete
  , get
  , post
  , put
  , buildRequest
  , performRequest
  , handleResponse
  , decodeValue
  ) where

import Data.Aeson (FromJSON, eitherDecode)
import Data.ByteString.Char8 (unpack)
import Data.ByteString.Lazy (ByteString)
import Network.HTTP.Client
  (Request, Response, method, parseRequest, responseBody)
import Network.HTTP.Types
  ( Method
  , Query
  , QueryLike
  , methodDelete
  , methodGet
  , methodPost
  , methodPut
  , renderQuery
  , toQuery
  )
import Strive.Aliases (Result)
import Strive.Client (Client(client_accessToken, client_requester))

-- | Perform an HTTP DELETE request.
delete :: (QueryLike q, FromJSON j) => Client -> String -> q -> IO (Result j)
delete :: forall q j.
(QueryLike q, FromJSON j) =>
Client -> String -> q -> IO (Result j)
delete = forall q j.
(QueryLike q, FromJSON j) =>
Method -> Client -> String -> q -> IO (Result j)
http Method
methodDelete

-- | Perform an HTTP GET request.
get :: (QueryLike q, FromJSON j) => Client -> String -> q -> IO (Result j)
get :: forall q j.
(QueryLike q, FromJSON j) =>
Client -> String -> q -> IO (Result j)
get = forall q j.
(QueryLike q, FromJSON j) =>
Method -> Client -> String -> q -> IO (Result j)
http Method
methodGet

-- | Perform an HTTP POST request.
post :: (QueryLike q, FromJSON j) => Client -> String -> q -> IO (Result j)
post :: forall q j.
(QueryLike q, FromJSON j) =>
Client -> String -> q -> IO (Result j)
post = forall q j.
(QueryLike q, FromJSON j) =>
Method -> Client -> String -> q -> IO (Result j)
http Method
methodPost

-- | Perform an HTTP PUT request.
put :: (QueryLike q, FromJSON j) => Client -> String -> q -> IO (Result j)
put :: forall q j.
(QueryLike q, FromJSON j) =>
Client -> String -> q -> IO (Result j)
put = forall q j.
(QueryLike q, FromJSON j) =>
Method -> Client -> String -> q -> IO (Result j)
http Method
methodPut

-- | Perform an HTTP request.
http
  :: (QueryLike q, FromJSON j)
  => Method
  -> Client
  -> String
  -> q
  -> IO (Result j)
http :: forall q j.
(QueryLike q, FromJSON j) =>
Method -> Client -> String -> q -> IO (Result j)
http Method
httpMethod Client
client String
resource q
query = do
  Request
request <- forall q.
QueryLike q =>
Method -> Client -> String -> q -> IO Request
buildRequest Method
httpMethod Client
client String
resource q
query
  Response ByteString
response <- Client -> Request -> IO (Response ByteString)
performRequest Client
client Request
request
  forall (m :: * -> *) a. Monad m => a -> m a
return (forall j. FromJSON j => Response ByteString -> Result j
handleResponse Response ByteString
response)

-- | Build a request.
buildRequest :: QueryLike q => Method -> Client -> String -> q -> IO Request
buildRequest :: forall q.
QueryLike q =>
Method -> Client -> String -> q -> IO Request
buildRequest Method
httpMethod Client
client String
resource q
query = do
  Request
request <- forall (m :: * -> *). MonadThrow m => String -> m Request
parseRequest (forall q. QueryLike q => Client -> String -> q -> String
buildUrl Client
client String
resource q
query)
  forall (m :: * -> *) a. Monad m => a -> m a
return Request
request { method :: Method
method = Method
httpMethod }

-- | Build a URL.
buildUrl :: QueryLike q => Client -> String -> q -> String
buildUrl :: forall q. QueryLike q => Client -> String -> q -> String
buildUrl Client
client String
resource q
query = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [ String
"https://www.strava.com/"
  , String
resource
  , Method -> String
unpack (Bool -> Query -> Method
renderQuery Bool
True (Client -> Query
buildQuery Client
client forall a. Semigroup a => a -> a -> a
<> forall a. QueryLike a => a -> Query
toQuery q
query))
  ]

-- | Build a query.
buildQuery :: Client -> Query
buildQuery :: Client -> Query
buildQuery Client
client = forall a. QueryLike a => a -> Query
toQuery [(String
"access_token", Client -> String
client_accessToken Client
client)]

-- | Actually perform an HTTP request.
performRequest :: Client -> Request -> IO (Response ByteString)
performRequest :: Client -> Request -> IO (Response ByteString)
performRequest = Client -> Request -> IO (Response ByteString)
client_requester

-- | Handle decoding a potentially failed response.
handleResponse :: FromJSON j => Response ByteString -> Result j
handleResponse :: forall j. FromJSON j => Response ByteString -> Result j
handleResponse Response ByteString
response = case forall j. FromJSON j => Response ByteString -> Either String j
decodeValue Response ByteString
response of
  Left String
message -> forall a b. a -> Either a b
Left (Response ByteString
response, String
message)
  Right j
value -> forall a b. b -> Either a b
Right j
value

-- | Decode a response body as JSON.
decodeValue :: FromJSON j => Response ByteString -> Either String j
decodeValue :: forall j. FromJSON j => Response ByteString -> Either String j
decodeValue Response ByteString
response = forall a. FromJSON a => ByteString -> Either String a
eitherDecode (forall body. Response body -> body
responseBody Response ByteString
response)