polysemy-http-0.13.1.0: Polysemy effects for HTTP clients
Safe HaskellNone
LanguageGHC2021

Polysemy.Http.Data.Response

Description

 
Synopsis

Documentation

pattern Success :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 2xx status.

pattern Info :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 1xx status.

data Response b Source #

The response produced by Http.

Constructors

Response 

Fields

Instances

Instances details
Generic (Response b) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

Associated Types

type Rep (Response b) 
Instance details

Defined in Polysemy.Http.Data.Response

type Rep (Response b) = D1 ('MetaData "Response" "Polysemy.Http.Data.Response" "polysemy-http-0.13.1.0-HslaAdsBwfBFVTgN9RdJNp" 'False) (C1 ('MetaCons "Response" 'PrefixI 'True) ((S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "headers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Header]) :*: S1 ('MetaSel ('Just "cookies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CookieJar))))

Methods

from :: Response b -> Rep (Response b) x #

to :: Rep (Response b) x -> Response b #

Show (Response BodyReader) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

Show b => Show (Response b) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

Methods

showsPrec :: Int -> Response b -> ShowS #

show :: Response b -> String #

showList :: [Response b] -> ShowS #

Eq b => Eq (Response b) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

Methods

(==) :: Response b -> Response b -> Bool #

(/=) :: Response b -> Response b -> Bool #

type Rep (Response b) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

type Rep (Response b) = D1 ('MetaData "Response" "Polysemy.Http.Data.Response" "polysemy-http-0.13.1.0-HslaAdsBwfBFVTgN9RdJNp" 'False) (C1 ('MetaCons "Response" 'PrefixI 'True) ((S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "headers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Header]) :*: S1 ('MetaSel ('Just "cookies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CookieJar))))

pattern Client :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 4xx status.

pattern Redirect :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 3xx status.

pattern Server :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 5xx status.

data Status #

HTTP Status.

Only the statusCode is used for comparisons.

Please use mkStatus to create status codes from code and message, or the Enum instance or the status code constants (like ok200). There might be additional record members in the future.

Note that the Show instance is only for debugging.

Constructors

Status Int ByteString 

Instances

Instances details
Data Status

Since: http-types-0.12.4

Instance details

Defined in Network.HTTP.Types.Status

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Status -> c Status #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Status #

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Status) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status) #

gmapT :: (forall b. Data b => b -> b) -> Status -> Status #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQ :: (forall d. Data d => d -> u) -> Status -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Status -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

Bounded Status

Since: http-types-0.11

Instance details

Defined in Network.HTTP.Types.Status

Enum Status

Be advised, that when using the "enumFrom*" family of methods or ranges in lists, it will generate all possible status codes.

E.g. [status100 .. status200] generates Statuses of 100, 101, 102 .. 198, 199, 200

The statuses not included in this library will have an empty message.

Since: http-types-0.7.3

Instance details

Defined in Network.HTTP.Types.Status

Generic Status 
Instance details

Defined in Network.HTTP.Types.Status

Associated Types

type Rep Status

Since: http-types-0.12.4

Instance details

Defined in Network.HTTP.Types.Status

type Rep Status = D1 ('MetaData "Status" "Network.HTTP.Types.Status" "http-types-0.12.4-5BurDxzsqYc48SPMcyRZOH" 'False) (C1 ('MetaCons "Status" 'PrefixI 'True) (S1 ('MetaSel ('Just "statusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "statusMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

Show Status 
Instance details

Defined in Network.HTTP.Types.Status

Eq Status

A Status is equal to another Status if the status codes are equal.

Instance details

Defined in Network.HTTP.Types.Status

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Ord Status

Statuses are ordered according to their status codes only.

Instance details

Defined in Network.HTTP.Types.Status

type Rep Status

Since: http-types-0.12.4

Instance details

Defined in Network.HTTP.Types.Status

type Rep Status = D1 ('MetaData "Status" "Network.HTTP.Types.Status" "http-types-0.12.4-5BurDxzsqYc48SPMcyRZOH" 'False) (C1 ('MetaCons "Status" 'PrefixI 'True) (S1 ('MetaSel ('Just "statusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "statusMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))