{-# options_haddock prune #-}

-- |Description: Response Data Types, Internal
module Polysemy.Http.Data.Response (
  module Polysemy.Http.Data.Response,
  Status(Status),
) where

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

import Polysemy.Http.Data.Header (Header)

-- |The response produced by 'Polysemy.Http.Effect.Http'.
data Response b =
  Response {
    -- |Uses the type from 'Network.HTTP' for convenience.
    forall b. Response b -> Status
status :: Status,
    -- |The body might be evaluated or an 'IO' action.
    forall b. Response b -> b
body :: b,
    -- |Does not use the type from 'Network.HTTP' because it is an alias.
    forall b. Response b -> [Header]
headers :: [Header],
    -- |The native cookie jar.
    forall b. Response b -> CookieJar
cookies :: CookieJar
  }
  deriving stock (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
$cshowsPrec :: forall b. Show b => Int -> Response b -> ShowS
showsPrec :: Int -> Response b -> ShowS
$cshow :: forall b. Show b => Response b -> String
show :: Response b -> String
$cshowList :: forall b. Show b => [Response b] -> ShowS
showList :: [Response b] -> ShowS
Show, (forall x. Response b -> Rep (Response b) x)
-> (forall x. Rep (Response b) x -> Response b)
-> Generic (Response b)
forall x. Rep (Response b) x -> Response b
forall x. Response b -> Rep (Response b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (Response b) x -> Response b
forall b x. Response b -> Rep (Response b) x
$cfrom :: forall b x. Response b -> Rep (Response b) x
from :: forall x. Response b -> Rep (Response b) x
$cto :: forall b x. Rep (Response b) x -> Response b
to :: forall x. Rep (Response b) x -> Response b
Generic)

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

instance Eq b => Eq (Response b) where
  Response Status
ls b
lb [Header]
lh CookieJar
_ == :: Response b -> Response b -> Bool
== Response Status
rs b
rb [Header]
rh CookieJar
_ =
    Status
ls Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
== Status
rs Bool -> Bool -> Bool
&& b
lb b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
rb Bool -> Bool -> Bool
&& [Header]
lh [Header] -> [Header] -> Bool
forall a. Eq a => a -> a -> Bool
== [Header]
rh

-- |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) -> ((# #) -> 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) -> ((# #) -> 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) -> ((# #) -> 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) -> ((# #) -> 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) -> ((# #) -> r) -> r
Server s b h <- Response s@(statusIsServerError -> True) b h _