req package:req

HTTP client library HTTP client library.
Make an HTTP request. The function takes 5 arguments, 4 of which specify required parameters and the final Option argument is a collection of optional parameters. Let's go through all the arguments first: req method url body response options. method is an HTTP method such as GET or POST. The documentation has a dedicated section about HTTP methods below. url is a Url that describes location of resource you want to interact with. body is a body option such as NoReqBody or ReqBodyJson. The tutorial has a section about HTTP bodies, but usage is very straightforward and should be clear from the examples. response is a type hint how to make and interpret response of an HTTP request. Out-of-the-box it can be the following: Finally, options is a Monoid that holds a composite Option for all other optional settings like query parameters, headers, non-standard port number, etc. There are quite a few things you can put there, see the corresponding section in the documentation. If you don't need anything at all, pass mempty. Note that if you use req to do all your requests, connection sharing and reuse is done for you automatically. See the examples below to get on the speed quickly.

Examples

First, this is a piece of boilerplate that should be in place before you try the examples:
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}

module Main (main) where

import Control.Monad
import Control.Monad.IO.Class
import Data.Aeson
import Data.Maybe (fromJust)
import Data.Monoid ((<>))
import Data.Text (Text)
import GHC.Generics
import Network.HTTP.Req
import qualified Data.ByteString.Char8 as B
import qualified Text.URI as URI
We will be making requests against the https://httpbin.org service. Make a GET request, grab 5 random bytes:
main :: IO ()
main = runReq defaultHttpConfig $ do
let n :: Int
n = 5
bs <- req GET (https "httpbin.org" /: "bytes" /~ n) NoReqBody bsResponse mempty
liftIO $ B.putStrLn (responseBody bs)
The same, but now we use a query parameter named "seed" to control seed of the generator:
main :: IO ()
main = runReq defaultHttpConfig $ do
let n, seed :: Int
n    = 5
seed = 100
bs <- req GET (https "httpbin.org" /: "bytes" /~ n) NoReqBody bsResponse $
"seed" =: seed
liftIO $ B.putStrLn (responseBody bs)
POST JSON data and get some info about the POST request:
data MyData = MyData
{ size  :: Int
, color :: Text
} deriving (Show, Generic)

instance ToJSON MyData
instance FromJSON MyData

main :: IO ()
main = runReq defaultHttpConfig $ do
let myData = MyData
{ size  = 6
, color = "Green" }
v <- req POST (https "httpbin.org" /: "post") (ReqBodyJson myData) jsonResponse mempty
liftIO $ print (responseBody v :: Value)
Sending URL-encoded body:
main :: IO ()
main = runReq defaultHttpConfig $ do
let params =
"foo" =: ("bar" :: Text) <>
queryFlag "baz"
response <- req POST (https "httpbin.org" /: "post") (ReqBodyUrlEnc params) jsonResponse mempty
liftIO $ print (responseBody response :: Value)
Using various optional parameters and URL that is not known in advance:
main :: IO ()
main = runReq defaultHttpConfig $ do
-- This is an example of what to do when URL is given dynamically. Of
-- course in a real application you may not want to use 'fromJust'.
uri <- URI.mkURI "https://httpbin.org/get?foo=bar"
let (url, options) = fromJust (useHttpsURI uri)
response <- req GET url NoReqBody jsonResponse $
"from" =: (15 :: Int)           <>
"to"   =: (67 :: Int)           <>
basicAuth "username" "password" <>
options                         <> -- contains the ?foo=bar part
port 443 -- here you can put any port of course
liftIO $ print (responseBody response :: Value)
The documentation below is structured in such a way that the most important information is presented first: you learn how to do HTTP requests, how to embed them in the monad you have, and then it gives you details about less-common things you may want to know about. The documentation is written with sufficient coverage of details and examples, and it's designed to be a complete tutorial on its own.

About the library

Req is an HTTP client library that attempts to be easy-to-use, type-safe, and expandable. “Easy-to-use” means that the library is designed to be beginner-friendly so it's simple to add to your monad stack, intuitive to work with, well-documented, and does not get in your way. Doing HTTP requests is a common task and a Haskell library for this should be approachable and clear to beginners, thus certain compromises were made. For example, one cannot currently modify ManagerSettings of the default manager because the library always uses the same implicit global manager for simplicity and maximal connection sharing. There is a way to use your own manager with different settings, but it requires more typing. “Type-safe” means that the library tries to eliminate certain classes of errors. For example, we have correct-by-construction URLs; it is guaranteed that the user does not send the request body when using methods like GET or OPTIONS, and the amount of implicit assumptions is minimized by making the user specify their intentions in an explicit form. For example, it's not possible to avoid specifying the body or the method of a request. Authentication methods that assume HTTPS force the user to use HTTPS at the type level. “Expandable” refers to the ability to create new components without having to resort to hacking. For example, it's possible to define your own HTTP methods, create new ways to construct the body of a request, create new authorization options, perform a request in a different way, and create your own methods to parse a response.

Using with other libraries

  • You won't need the low-level interface of http-client most of the time, but when you do, it's better to do a qualified import, because http-client has naming conflicts with req.
  • For streaming of large request bodies see the companion package req-conduit: https://hackage.haskell.org/package/req-conduit.

Lightweight, no risk solution

The library uses the following mature packages under the hood to guarantee you the best experience: It's important to note that since we leverage well-known libraries that the whole Haskell ecosystem uses, there is no risk in using req. The machinery for performing requests is the same as with http-conduit and wreq. The only difference is the API.
A monad that allows us to run req in any IO-enabled monad without having to define new instances.
Mostly like req with respect to its arguments, but accepts a callback that allows to perform a request in arbitrary fashion. This function does not perform handling/wrapping exceptions, checking response (with httpConfigCheckResponse), and retrying. It only prepares Request and allows you to use it.
Create ReqBodyMultipart request body from a collection of Parts.
A version of req that does not use one of the predefined instances of HttpResponse but instead allows the user to consume Response BodyReader manually, in a custom way.
A version of req that takes a callback to modify the Request, but otherwise performs the request identically.
HTTP request body represented by a strict ByteString. Using of this body option does not set the Content-Type header.
This body option streams request body from a file. It is expected that the file size does not change during streaming. Using of this body option does not set the Content-Type header.
This body option allows us to use a JSON object as the request body—probably the most popular format right now. Just wrap a data type that is an instance of ToJSON type class and you are done: it will be converted to JSON and inserted as request body. This body option sets the Content-Type header to "application/json; charset=utf-8" value.
HTTP request body represented by a lazy ByteString. Using of this body option does not set the Content-Type header.
Multipart form data. Please consult the Network.HTTP.Client.MultipartFormData module for how to construct parts, then use reqBodyMultipart to create actual request body from the parts. reqBodyMultipart is the only way to get a value of the type ReqBodyMultipart, as its constructor is not exported on purpose.

Examples

import Control.Monad.IO.Class
import Data.Default.Class
import Network.HTTP.Req
import qualified Network.HTTP.Client.MultipartFormData as LM

main :: IO ()
main = runReq def $ do
body <-
reqBodyMultipart
[ LM.partBS "title" "My Image"
, LM.partFileSource "file1" "/tmp/image.jpg"
]
response <-
req POST (http "example.com" /: "post")
body
bsResponse
mempty
liftIO $ print (responseBody response)
URL-encoded body. This can hold a collection of parameters which are encoded similarly to query parameters at the end of query string, with the only difference that they are stored in request body. The similarity is reflected in the API as well, as you can use the same combinators you would use to add query parameters: (=:) and queryFlag. This body option sets the Content-Type header to "application/x-www-form-urlencoded" value.
This data type represents empty body of an HTTP request. This is the data type to use with HttpMethods that cannot have a body, as it's the only type for which ProvidesBody returns NoBody. Using of this body option does not set the Content-Type header.
How to get actual RequestBody.
This method allows us to optionally specify the value of Content-Type header that should be used with particular body option. By default it returns Nothing and so Content-Type is not set.
Run a computation in the Req monad with the given HttpConfig. In the case of an exceptional situation an HttpException will be thrown.
Perform an action using the global implicit Manager that the rest of the library uses. This allows to reuse connections that the Manager controls.