{-# options_haddock prune #-}
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)
data Response b =
Response {
Response b -> Status
_status :: Status,
Response b -> b
_body :: b,
:: [Header],
Response b -> CookieJar
_cookies :: CookieJar
}
deriving (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} }|]
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
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 _
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 _
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 _
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 _
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 _