module Polysemy.Http.Data.Response (
  module Polysemy.Http.Data.Response,
  Status(Status),
) where

import Network.HTTP.Client (BodyReader, CookieJar)
import Network.HTTP.Types (
  Status(Status),
  statusIsClientError,
  statusIsInformational,
  statusIsRedirection,
  statusIsServerError,
  statusIsSuccessful,
  )
import qualified Text.Show as Text (Show(show))

import Polysemy.Http.Data.Header (Header)

-- |The response produced by 'Polysemy.Http.Data.Http'.
data Response b =
  Response {
    -- |Uses the type from 'Network.HTTP' for convenience.
    Response b -> Status
_status :: Status,
    -- |The body might be evaluated or an 'IO' action.
    Response b -> b
_body :: b,
    -- |Does not use the type from 'Network.HTTP' because it is an alias.
    Response b -> [Header]
_headers :: [Header],
    -- |The native cookie jar.
    Response b -> CookieJar
_cookies :: CookieJar
  }
  deriving (Response b -> Response b -> Bool
(Response b -> Response b -> Bool)
-> (Response b -> Response b -> Bool) -> Eq (Response b)
forall b. Eq b => Response b -> Response b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Response b -> Response b -> Bool
$c/= :: forall b. Eq b => Response b -> Response b -> Bool
== :: Response b -> Response b -> Bool
$c== :: forall b. Eq b => Response b -> Response b -> Bool
Eq, Int -> Response b -> ShowS
[Response b] -> ShowS
Response b -> String
(Int -> Response b -> ShowS)
-> (Response b -> String)
-> ([Response b] -> ShowS)
-> Show (Response b)
forall b. Show b => Int -> Response b -> ShowS
forall b. Show b => [Response b] -> ShowS
forall b. Show b => Response b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Response b] -> ShowS
$cshowList :: forall b. Show b => [Response b] -> ShowS
show :: Response b -> String
$cshow :: forall b. Show b => Response b -> String
showsPrec :: Int -> Response b -> ShowS
$cshowsPrec :: forall b. Show b => Int -> Response b -> ShowS
Show)

instance {-# overlapping #-} Show (Response BodyReader) where
  show :: Response BodyReader -> String
show (Response Status
s BodyReader
_ [Header]
hs CookieJar
_) =
    [qt|StreamingResponse { status :: #{s}, headers :: #{hs} }|]

-- |Match on a response with a 1xx status.
pattern Info ::
  Status ->
  b ->
  [Header] ->
  Response b
pattern $mInfo :: forall r b.
Response b -> (Status -> b -> [Header] -> r) -> (Void# -> r) -> r
Info s b h <- Response s@(statusIsInformational -> True) b h _

-- |Match on a response with a 2xx status.
pattern Success ::
  Status ->
  b ->
  [Header] ->
  Response b
pattern $mSuccess :: forall r b.
Response b -> (Status -> b -> [Header] -> r) -> (Void# -> r) -> r
Success s b h <- Response s@(statusIsSuccessful -> True) b h _

-- |Match on a response with a 3xx status.
pattern Redirect ::
  Status ->
  b ->
  [Header] ->
  Response b
pattern $mRedirect :: forall r b.
Response b -> (Status -> b -> [Header] -> r) -> (Void# -> r) -> r
Redirect s b h <- Response s@(statusIsRedirection -> True) b h _

-- |Match on a response with a 4xx status.
pattern Client ::
  Status ->
  b ->
  [Header] ->
  Response b
pattern $mClient :: forall r b.
Response b -> (Status -> b -> [Header] -> r) -> (Void# -> r) -> r
Client s b h <- Response s@(statusIsClientError -> True) b h _

-- |Match on a response with a 5xx status.
pattern Server ::
  Status ->
  b ->
  [Header] ->
  Response b
pattern $mServer :: forall r b.
Response b -> (Status -> b -> [Header] -> r) -> (Void# -> r) -> r
Server s b h <- Response s@(statusIsServerError -> True) b h _