module Polysemy.Http.Json where

import Control.Lens ((%~))

import Polysemy.Http.Data.Header (HeaderName, HeaderValue)
import qualified Polysemy.Http.Data.Http as Http
import Polysemy.Http.Data.Http (Http)
import Polysemy.Http.Data.HttpError (HttpError)
import qualified Polysemy.Http.Data.Request as Request
import Polysemy.Http.Data.Request (Request)
import Polysemy.Http.Data.Response (Response)

jsonContentType :: (HeaderName, HeaderValue)
jsonContentType :: (HeaderName, HeaderValue)
jsonContentType =
  (HeaderName
"content-type", HeaderValue
"application/json")

jsonRequest ::
  Member (Http c) r =>
  Request ->
  Sem r (Either HttpError (Response LByteString))
jsonRequest :: Request -> Sem r (Either HttpError (Response LByteString))
jsonRequest =
  Request -> Sem r (Either HttpError (Response LByteString))
forall c (r :: [(* -> *) -> * -> *]).
Member (Http c) r =>
Request -> Sem r (Either HttpError (Response LByteString))
Http.request (Request -> Sem r (Either HttpError (Response LByteString)))
-> (Request -> Request)
-> Request
-> Sem r (Either HttpError (Response LByteString))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([(HeaderName, HeaderValue)]
 -> Identity [(HeaderName, HeaderValue)])
-> Request -> Identity Request
forall c. HasRequest c => Lens' c [(HeaderName, HeaderValue)]
Request.headers (([(HeaderName, HeaderValue)]
  -> Identity [(HeaderName, HeaderValue)])
 -> Request -> Identity Request)
-> ([(HeaderName, HeaderValue)] -> [(HeaderName, HeaderValue)])
-> Request
-> Request
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ((HeaderName, HeaderValue)
jsonContentType (HeaderName, HeaderValue)
-> [(HeaderName, HeaderValue)] -> [(HeaderName, HeaderValue)]
forall a. a -> [a] -> [a]
:))