nri-http-0.3.0.0: Make Elm style HTTP requests
Safe HaskellNone
LanguageHaskell2010

Http

Description

Making HTTP requests using an API inspired by Elm's elm/http.

Synopsis

Handlers

data Handler Source #

A handler for making HTTP requests.

handler :: Acquire Handler Source #

Create a Handler for making HTTP requests.

Requests

get :: (Typeable x, Typeable a) => Handler -> Text -> Expect' x a -> Task x a Source #

Create a GET request.

post :: (Typeable x, Typeable a) => Handler -> Text -> Body -> Expect' x a -> Task x a Source #

Create a POST request.

request :: (Typeable x, Typeable expect) => Handler -> Request' x expect -> Task x expect Source #

Create a custom request.

data Request' x a Source #

A custom request.

Constructors

Request 

Fields

type Request a = Request' Error a Source #

A simple request with the built-in Error type.

data Error Source #

A Request can fail in a couple of ways:

  • BadUrl means you did not provide a valid URL.
  • Timeout means it took too long to get a response.
  • NetworkError means the user turned off their wifi, went in a cave, etc.
  • BadStatus means you got a response back, but the status code indicates failure.
  • BadBody means you got a response back with a nice status code, but the body of the response was something unexpected. The Text in this cse is the debugging message that explains what went wrong with your JSONT decoder or whatever.

Instances

Instances details
Eq Error Source # 
Instance details

Defined in Http.Internal

Methods

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

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

Show Error Source # 
Instance details

Defined in Http.Internal

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Generic Error Source # 
Instance details

Defined in Http.Internal

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

ToJSON Error Source # 
Instance details

Defined in Http.Internal

Exception Error Source # 
Instance details

Defined in Http.Internal

type Rep Error Source # 
Instance details

Defined in Http.Internal

Header

data Header Source #

An HTTP header for configuration requests.

Instances

Instances details
Eq Header Source # 
Instance details

Defined in Http.Internal

Methods

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

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

Show Header Source # 
Instance details

Defined in Http.Internal

header :: Text -> Text -> Header Source #

Create a Header.

Body

data Body Source #

Represents the body of a Request.

emptyBody :: Body Source #

Create an empty body for your Request. This is useful for GET requests and POST requests where you are not sending any data.

stringBody :: Text -> Text -> Body Source #

Put some string in the body of your Request.

The first argument is a MIME type of the body. Some servers are strict about this!

jsonBody :: ToJSON body => body -> Body Source #

Put some JSON value in the body of your Request. This will automatically add the Content-Type: application/json header.

bytesBody :: Text -> ByteString -> Body Source #

Put some Bytes in the body of your Request. This allows you to use ByteString to have full control over the binary representation of the data you are sending.

The first argument is a MIME type of the body. In other scenarios you may want to use MIME types like imagepng or imagejpeg instead.

Expect

type Expect a = Expect' Error a Source #

A simple logic for interpreting a response body with the built-in Error type.

expectJson :: FromJSON a => Expect a Source #

Expect the response body to be JSON.

expectText :: Expect Text Source #

Expect the response body to be a Text.

expectWhatever :: Expect () Source #

Expect the response body to be whatever. It does not matter. Ignore it!

Elaborate Expectations

data Expect' x a Source #

Logic for interpreting a response body.

expectTextResponse :: (Response Text -> Result x a) -> Expect' x a Source #

Expect a Response with a Text body.

expectBytesResponse :: (Response ByteString -> Result x a) -> Expect' x a Source #

Expect a Response with a ByteString body

data Response body Source #

A Response can come back a couple different ways:

  • BadUrl_ — you did not provide a valid URL.
  • Timeout_ — it took too long to get a response.
  • NetworkError_ — the user turned off their wifi, went in a cave, etc.
  • BadStatus_ — a response arrived, but the status code indicates failure.
  • GoodStatus_ — a response arrived with a nice status code!
  • The type of the body depends on whether you use expectStringResponse or expectBytesResponse.

Instances

Instances details
Eq body => Eq (Response body) Source # 
Instance details

Defined in Http.Internal

Methods

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

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

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

Defined in Http.Internal

Methods

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

show :: Response body -> String #

showList :: [Response body] -> ShowS #

Generic (Response body) Source # 
Instance details

Defined in Http.Internal

Associated Types

type Rep (Response body) :: Type -> Type #

Methods

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

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

ToJSON body => ToJSON (Response body) Source # 
Instance details

Defined in Http.Internal

(Typeable body, Show body) => Exception (Response body) Source # 
Instance details

Defined in Http.Internal

type Rep (Response body) Source # 
Instance details

Defined in Http.Internal

data Metadata Source #

Instances

Instances details
Eq Metadata Source # 
Instance details

Defined in Http.Internal

Show Metadata Source # 
Instance details

Defined in Http.Internal

Generic Metadata Source # 
Instance details

Defined in Http.Internal

Associated Types

type Rep Metadata :: Type -> Type #

Methods

from :: Metadata -> Rep Metadata x #

to :: Rep Metadata x -> Metadata #

ToJSON Metadata Source # 
Instance details

Defined in Http.Internal

type Rep Metadata Source # 
Instance details

Defined in Http.Internal

type Rep Metadata = D1 ('MetaData "Metadata" "Http.Internal" "nri-http-0.3.0.0-inplace" 'False) (C1 ('MetaCons "Metadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "metadataStatusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "metadataStatusText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "metadataHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Dict Text Text)))))

Use with external libraries

withThirdParty :: Handler -> (Manager -> Task e a) -> Task e a Source #

Third party libraries that make HTTP requests often take a Manager. This helper allows us to call such a library using a Handler.

The benefit over using this over using a separate Manager for the external library, is that withThirdParty will ensure HTTP requests made by the external library will get logged.

withThirdPartyIO :: LogHandler -> Handler -> (Manager -> IO a) -> IO a Source #

Like withThirdParty, but runs in IO.