| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Freckle.App.Http
Description
Centralized module for making HTTP requests from the backend
These functions:
- Do not throw exceptions on non-200
 - May throw for other 
HttpExceptioncases (e.g.ConnectionTimeout) - Handle 429-
Retry-Infor you - Capture decoding failures with 
Eithervalues as theResponsebody 
Examples
Make request, retry on 429s, and parse the body as JSON.
-- Throws, but only on a complete failure to perform the request resp <-httpJson$parseRequest_"https://example.com" -- Safe accessgetResponseBodyresp :: EitherHttpDecodeErrora -- Unsafe access (throws on Left)getResponseBodyUnsaferesp :: m a
httpLbs can be used to get a raw response (without risk of decoding
 errors), and httpDecode can be used to supply your own decoding function
 (e.g. for CSV).
Interact with a paginated endpoint that uses Link, combining all the pages
 monoidally (e.g. concat) and throwing on any decoding errors.
httpPaginatedhttpJsongetResponseBodyUnsafe$parseRequest_"https://..."
Decoding errors can be handled differently by adjusting what Monoid you
 convert each page's response into:
httpPaginatedhttpJsonfromResponseLenient $parseRequest_"https://..." fromResponseLenient :: MonadLogger m => Response (Either e [MyJsonThing]) -> m [MyJsonThing] fromResponseLenient r = case getResponseBody r of Left _ -> [] <$ logWarn "..." Right a -> pure a
See Freckle.Http.App.Paginate to process requested pages in a streaming
 fashion, or perform pagination based on somethign other than Link.
Synopsis
- httpJson :: (MonadIO m, FromJSON a) => Request -> m (Response (Either HttpDecodeError a))
 - data HttpDecodeError = HttpDecodeError {}
 - httpDecode :: MonadIO m => (ByteString -> Either (NonEmpty String) a) -> Request -> m (Response (Either HttpDecodeError a))
 - httpLbs :: MonadIO m => Request -> m (Response ByteString)
 - httpNoBody :: MonadIO m => Request -> m (Response ())
 - httpPaginated :: (MonadIO m, Monoid b) => (Request -> m (Response a)) -> (Response a -> m b) -> Request -> m b
 - sourcePaginated :: MonadIO m => (Request -> m (Response body)) -> Request -> ConduitT i (Response body) m ()
 - data Request
 - parseRequest :: MonadThrow m => String -> m Request
 - parseRequest_ :: String -> Request
 - addRequestHeader :: HeaderName -> ByteString -> Request -> Request
 - addAcceptHeader :: ByteString -> Request -> Request
 - addBearerAuthorizationHeader :: ByteString -> Request -> Request
 - addToRequestQueryString :: Query -> Request -> Request
 - setRequestBasicAuth :: ByteString -> ByteString -> Request -> Request
 - setRequestBodyJSON :: ToJSON a => a -> Request -> Request
 - setRequestBodyURLEncoded :: [(ByteString, ByteString)] -> Request -> Request
 - setRequestCheckStatus :: Request -> Request
 - setRequestPath :: ByteString -> Request -> Request
 - data Response body
 - getResponseStatus :: Response a -> Status
 - getResponseBody :: Response a -> a
 - getResponseBodyUnsafe :: (MonadIO m, Exception e) => Response (Either e a) -> m a
 - data HttpException
 - httpExceptionIsInformational :: HttpException -> Bool
 - httpExceptionIsRedirection :: HttpException -> Bool
 - httpExceptionIsClientError :: HttpException -> Bool
 - httpExceptionIsServerError :: HttpException -> Bool
 - data Status
 - statusCode :: Status -> Int
 - statusIsInformational :: Status -> Bool
 - statusIsSuccessful :: Status -> Bool
 - statusIsRedirection :: Status -> Bool
 - statusIsClientError :: Status -> Bool
 - statusIsServerError :: Status -> Bool
 
Documentation
httpJson :: (MonadIO m, FromJSON a) => Request -> m (Response (Either HttpDecodeError a)) Source #
Request and decode a response as JSON
data HttpDecodeError Source #
Constructors
| HttpDecodeError | |
Fields 
  | |
Instances
| Eq HttpDecodeError Source # | |
Defined in Freckle.App.Http Methods (==) :: HttpDecodeError -> HttpDecodeError -> Bool # (/=) :: HttpDecodeError -> HttpDecodeError -> Bool #  | |
| Show HttpDecodeError Source # | |
Defined in Freckle.App.Http Methods showsPrec :: Int -> HttpDecodeError -> ShowS # show :: HttpDecodeError -> String # showList :: [HttpDecodeError] -> ShowS #  | |
| Exception HttpDecodeError Source # | |
Defined in Freckle.App.Http Methods toException :: HttpDecodeError -> SomeException #  | |
httpDecode :: MonadIO m => (ByteString -> Either (NonEmpty String) a) -> Request -> m (Response (Either HttpDecodeError a)) Source #
Request and decode a response
httpLbs :: MonadIO m => Request -> m (Response ByteString) Source #
Request a lazy ByteString, handling 429 retries
httpNoBody :: MonadIO m => Request -> m (Response ()) Source #
Make a Request ignoring the response, but handling 429 retries
httpPaginated :: (MonadIO m, Monoid b) => (Request -> m (Response a)) -> (Response a -> m b) -> Request -> m b Source #
Request all pages of a paginated endpoint into a big list
This uses sourcePaginated, and so reads a Link header. To do otherwise,
 drop down to sourcePaginatedBy directly.
The second argument is used to extract the data to combine out of the
 response. This is particularly useful for Either values, like you may get
 from httpJson. It lives in m to support functions such as getResponseBodyUnsafe.
Arguments
| :: MonadIO m | |
| => (Request -> m (Response body)) | Run one request  | 
| -> Request | Initial request  | 
| -> ConduitT i (Response body) m () | 
Stream pages of a paginated response, using Link to find next pages
Request builders
All information on how to connect to a host and what should be sent in the HTTP request.
If you simply wish to download from a URL, see parseRequest.
The constructor for this data type is not exposed. Instead, you should use
 either the defaultRequest value, or parseRequest to
 construct from a URL, and then use the records below to make modifications.
 This approach allows http-client to add configuration options without
 breaking backwards compatibility.
For example, to construct a POST request, you could do something like:
initReq <- parseRequest "http://www.example.com/path"
let req = initReq
            { method = "POST"
            }For more information, please see http://www.yesodweb.com/book/settings-types.
Since 0.1.0
parseRequest :: MonadThrow m => String -> m Request #
Convert a URL into a Request.
This function defaults some of the values in Request, such as setting method to
 GET and requestHeaders to [].
Since this function uses MonadThrow, the return monad can be anything that is
 an instance of MonadThrow, such as IO or Maybe.
You can place the request method at the beginning of the URL separated by a space, e.g.:
@@
 parseRequest "POST http://httpbin.org/post"
 @@
Note that the request method must be provided as all capital letters.
A Request created by this function won't cause exceptions on non-2XX
 response status codes.
To create a request which throws on non-2XX status codes, see parseUrlThrow
Since: http-client-0.4.30
parseRequest_ :: String -> Request #
Same as parseRequest, but parse errors cause an impure exception.
 Mostly useful for static strings which are known to be correctly
 formatted.
Request modifiers
addRequestHeader :: HeaderName -> ByteString -> Request -> Request #
Add a request header name/value combination
Since: http-conduit-2.1.10
addAcceptHeader :: ByteString -> Request -> Request Source #
addToRequestQueryString :: Query -> Request -> Request #
Add to the existing query string parameters.
Since: http-conduit-2.3.5
Arguments
| :: ByteString | username  | 
| -> ByteString | password  | 
| -> Request | |
| -> Request | 
Set basic auth with the given username and password
Since: http-conduit-2.1.10
setRequestBodyJSON :: ToJSON a => a -> Request -> Request #
Set the request body as a JSON value
Note: This will not modify the request method. For that, please use
 requestMethod. You likely don't want the default of GET.
This also sets the Content-Type to application/json; charset=utf-8
NOTE: Depends on the aeson cabal flag being enabled
Since: http-conduit-2.1.10
setRequestBodyURLEncoded :: [(ByteString, ByteString)] -> Request -> Request #
Set the request body as URL encoded data
Note: This will change the request method to POST and set the content-type
 to application/x-www-form-urlencoded
Since: http-conduit-2.1.10
setRequestCheckStatus :: Request -> Request #
Modify the request so that non-2XX status codes generate a runtime
 StatusCodeException, by using throwErrorStatusCodes
Since: http-client-0.5.13
setRequestPath :: ByteString -> Request -> Request #
Lens for the requested path info of the request
Since: http-conduit-2.1.10
Response accessors
A simple representation of the HTTP response.
Since 0.1.0
Instances
| Functor Response | |
| Foldable Response | |
Defined in Network.HTTP.Client.Types Methods fold :: Monoid m => Response m -> m # foldMap :: Monoid m => (a -> m) -> Response a -> m # foldMap' :: Monoid m => (a -> m) -> Response a -> m # foldr :: (a -> b -> b) -> b -> Response a -> b # foldr' :: (a -> b -> b) -> b -> Response a -> b # foldl :: (b -> a -> b) -> b -> Response a -> b # foldl' :: (b -> a -> b) -> b -> Response a -> b # foldr1 :: (a -> a -> a) -> Response a -> a # foldl1 :: (a -> a -> a) -> Response a -> a # elem :: Eq a => a -> Response a -> Bool # maximum :: Ord a => Response a -> a # minimum :: Ord a => Response a -> a #  | |
| Traversable Response | |
Defined in Network.HTTP.Client.Types  | |
| Show body => Show (Response body) | |
getResponseStatus :: Response a -> Status #
Get the status of the response
Since: http-conduit-2.1.10
getResponseBody :: Response a -> a #
Get the response body
Since: http-conduit-2.1.10
Unsafe access
getResponseBodyUnsafe :: (MonadIO m, Exception e) => Response (Either e a) -> m a Source #
Read an Either response body, throwing any Left as an exception
If you plan to use this function, and haven't built your decoding to handle
 error response bodies too, you'll want to use setRequestCheckStatus so that
 you see status-code exceptions before HttpDecodeErrors.
Exceptions
data HttpException #
An exception which may be generated by this library
Since: http-client-0.5.0
Constructors
| HttpExceptionRequest Request HttpExceptionContent | Most exceptions are specific to a  Since: http-client-0.5.0  | 
| InvalidUrlException String String | A URL (first field) is invalid for a given reason (second argument). Since: http-client-0.5.0  | 
Instances
| Show HttpException | |
Defined in Network.HTTP.Client.Types Methods showsPrec :: Int -> HttpException -> ShowS # show :: HttpException -> String # showList :: [HttpException] -> ShowS #  | |
| Exception HttpException | |
Defined in Network.HTTP.Client.Types Methods toException :: HttpException -> SomeException # fromException :: SomeException -> Maybe HttpException # displayException :: HttpException -> String #  | |
Predicates useful for handling HttpExceptions
For example, given a function guarded, which returns Just a given value
 when a predicate holds for it (otherwise Nothing), you can add
 error-handling specific to exceptions caused by 4XX responses:
handleJust(guardedhttpExceptionIsClientError) handle4XXError $ do resp <-httpJson$setRequestCheckStatus$ parseRequest_ "http://..." body <-getResponseBodyUnsaferesp -- ...
Network.HTTP.Types re-exports
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.
statusCode :: Status -> Int #
statusIsInformational :: Status -> Bool #
Informational class
statusIsSuccessful :: Status -> Bool #
Successful class
statusIsRedirection :: Status -> Bool #
Redirection class
statusIsClientError :: Status -> Bool #
Client Error class
statusIsServerError :: Status -> Bool #
Server Error class