| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.IO.Streams.HTTP
Contents
Description
Here is an example GET request that streams the response body to standard output with OpenSSL:
{-# LANGUAGE OverloadedStrings #-}
module Main where
import qualified System.IO.Streams as Streams
import System.IO.Streams.HTTP ( opensslManagerSettings
, parseUrl
, withManager
, withHTTP
, responseBody
, withOpenSSL
, context
, requestBody
, stream
, method
)
------------------------------------------------------------------------------
-- | GET test (openssl)
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)
------------------------------------------------------------------------------
-- | POST test (tls)
post :: IO ()
post = withOpenSSL $ do
let settings = opensslManagerSettings context
req <- parseUrl "https://google.com"
let request = req { method = "POST"
, requestBody = stream $ Streams.fromLazyByteString "body"
}
withManager settings $ \mgr ->
withHTTP req mgr $ \resp ->
Streams.supplyTo Streams.stdout (responseBody resp)- module Network.HTTP.Client
- module Network.HTTP.Client.OpenSSL
- module OpenSSL
- module OpenSSL.Session
- withHTTP :: Request -> Manager -> (Response (InputStream ByteString) -> IO a) -> IO a
- streamN :: Int64 -> IO (InputStream ByteString) -> RequestBody
- stream :: IO (InputStream ByteString) -> RequestBody
http-client
This module is a thin io-streams wrapper around the http-client and
http-client-openssl libraries.
If you'd rather use the tls library for encryption then compile
with the tls flag (i.e. cabal configure -ftls)
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-opensslprovides support for TLS connections (i.e. HTTPS).
module Network.HTTP.Client
module Network.HTTP.Client.OpenSSL
module OpenSSL
module OpenSSL.Session
io-streams Interface
withHTTP :: Request -> Manager -> (Response (InputStream ByteString) -> IO a) -> IO a Source
streamN :: Int64 -> IO (InputStream ByteString) -> RequestBody Source
Stream with N bytes exactly
stream :: IO (InputStream ByteString) -> RequestBody Source
Stream body of request