http-client-streams-0.1.0.0: http-client for io-streams supporting openssl

Safe HaskellNone
LanguageHaskell2010

System.IO.Streams.HTTP

Contents

Description

Here is an example GET request that streams the response body to standard output:

{-# LANGUAGE OverloadedStrings #-}
module Main where
 
import           OpenSSL                ( withOpenSSL )
import           OpenSSL.Session        ( context )
import qualified System.IO.Streams as Streams
import           System.IO.Streams.HTTP ( opensslManagerSettings
                                        , parseUrl
                                        , withManager
                                        , withHTTP
                                        , responseBody
                                        )
 
------------------------------------------------------------------------------
-- | OpenSSL test
main :: IO ()
main = withOpenSSL $ do
  let settings = opensslManagerSettings context
  req <- parseUrl "https://google.com"
  withManager settings $ \mgr ->
    withHTTP req mgr $ \resp ->
      Streams.supplyTo Streams.stdout (responseBody resp)

For non-streaming request bodies, study the RequestBody type, which also accepts strict / lazy bytestrings

Synopsis

http-client

This module is a thin io-streams wrapper around the http-client and http-client-openssl libraries.

Read the documentation in the Network.HTTP.Client module of the http-client library to learn about how to:

  • manage connections using connection pooling,
    • use more advanced request/response features,
    • handle exceptions, and:
    • manage cookies.

    http-client-openssl provides support for TLS connections (i.e. HTTPS).

io-streams Interface

withHTTP :: Request -> Manager -> (Response (InputStream ByteString) -> IO a) -> IO a Source

Send an HTTP Request and wait for an HTTP Response

streamN :: Int64 -> InputStream ByteString -> RequestBody Source

Stream with N bytes exactly

stream :: InputStream ByteString -> RequestBody Source

Stream body of request