Blame Network/HTTP.hs

Packit acf257
-----------------------------------------------------------------------------
Packit acf257
-- |
Packit acf257
-- Module      :  Network.HTTP
Packit acf257
-- Copyright   :  See LICENSE file
Packit acf257
-- License     :  BSD
Packit acf257
-- 
Packit acf257
-- Maintainer  :  Ganesh Sittampalam <ganesh@earth.li>
Packit acf257
-- Stability   :  experimental
Packit acf257
-- Portability :  non-portable (not tested)
Packit acf257
--
Packit acf257
-- The 'Network.HTTP' module provides a simple interface for sending and
Packit acf257
-- receiving content over HTTP in Haskell. Here's how to fetch a document from
Packit acf257
-- a URL and return it as a String:
Packit acf257
--
Packit acf257
-- >
Packit acf257
-- >    simpleHTTP (getRequest "http://www.haskell.org/") >>= fmap (take 100) . getResponseBody
Packit acf257
-- >        -- fetch document and return it (as a 'String'.)
Packit acf257
--
Packit acf257
-- Other functions let you control the submission and transfer of HTTP
Packit acf257
-- 'Request's and 'Response's more carefully, letting you integrate the use
Packit acf257
-- of 'Network.HTTP' functionality into your application.
Packit acf257
--
Packit acf257
-- The module also exports the main types of the package, 'Request' and 'Response',
Packit acf257
-- along with 'Header' and functions for working with these.
Packit acf257
--
Packit acf257
-- The actual functionality is implemented by modules in the @Network.HTTP.*@
Packit acf257
-- namespace, letting you either use the default implementation here
Packit acf257
-- by importing @Network.HTTP@ or, for more specific uses, selectively
Packit acf257
-- import the modules in @Network.HTTP.*@. To wit, more than one kind of
Packit acf257
-- representation of the bulk data that flows across a HTTP connection is 
Packit acf257
-- supported. (see "Network.HTTP.HandleStream".)
Packit acf257
-- 
Packit acf257
-- /NOTE:/ The 'Request' send actions will normalize the @Request@ prior to transmission.
Packit acf257
-- Normalization such as having the request path be in the expected form and, possibly,
Packit acf257
-- introduce a default @Host:@ header if one isn't already present.
Packit acf257
-- Normalization also takes the @"user:pass\@"@ portion out of the the URI,
Packit acf257
-- if it was supplied, and converts it into @Authorization: Basic$ header.
Packit acf257
-- If you do not 
Packit acf257
-- want the requests tampered with, but sent as-is, please import and use the
Packit acf257
-- the "Network.HTTP.HandleStream" or "Network.HTTP.Stream" modules instead. They
Packit acf257
-- export the same functions, but leaves construction and any normalization of 
Packit acf257
-- @Request@s to the user.
Packit acf257
--
Packit acf257
-- /NOTE:/ This package only supports HTTP; it does not support HTTPS.
Packit acf257
-- Attempts to use HTTPS result in an error.
Packit acf257
-----------------------------------------------------------------------------
Packit acf257
module Network.HTTP 
Packit acf257
       ( module Network.HTTP.Base
Packit acf257
       , module Network.HTTP.Headers
Packit acf257
Packit acf257
         {- the functionality that the implementation modules, 
Packit acf257
	    Network.HTTP.HandleStream and Network.HTTP.Stream,
Packit acf257
	    exposes:
Packit acf257
	 -}
Packit acf257
       , simpleHTTP      -- :: Request -> IO (Result Response)
Packit acf257
       , simpleHTTP_     -- :: Stream s => s -> Request -> IO (Result Response)
Packit acf257
       , sendHTTP        -- :: Stream s => s -> Request -> IO (Result Response)
Packit acf257
       , sendHTTP_notify -- :: Stream s => s -> Request -> IO () -> IO (Result Response)
Packit acf257
       , receiveHTTP     -- :: Stream s => s -> IO (Result Request)
Packit acf257
       , respondHTTP     -- :: Stream s => s -> Response -> IO ()
Packit acf257
Packit acf257
       , module Network.TCP
Packit acf257
       
Packit acf257
       , getRequest      -- :: String -> Request_String
Packit acf257
       , headRequest     -- :: String -> Request_String
Packit acf257
       , postRequest     -- :: String -> Request_String
Packit acf257
       , postRequestWithBody -- :: String -> String -> String -> Request_String
Packit acf257
       
Packit acf257
       , getResponseBody -- :: Result (Request ty) -> IO ty
Packit acf257
       , getResponseCode -- :: Result (Request ty) -> IO ResponseCode
Packit acf257
       ) where
Packit acf257
Packit acf257
-----------------------------------------------------------------
Packit acf257
------------------ Imports --------------------------------------
Packit acf257
-----------------------------------------------------------------
Packit acf257
Packit acf257
import Network.HTTP.Headers
Packit acf257
import Network.HTTP.Base
Packit acf257
import qualified Network.HTTP.HandleStream as S
Packit acf257
-- old implementation: import Network.HTTP.Stream
Packit acf257
import Network.TCP
Packit acf257
import Network.Stream ( Result )
Packit acf257
import Network.URI    ( parseURI )
Packit acf257
Packit acf257
import Data.Maybe ( fromMaybe )
Packit acf257
Packit acf257
{-
Packit acf257
 Note: if you switch over/back to using Network.HTTP.Stream here, you'll
Packit acf257
 have to wrap the results from 'openStream' as Connections via 'hstreamToConnection'
Packit acf257
 prior to delegating to the Network.HTTP.Stream functions.
Packit acf257
-}
Packit acf257
Packit acf257
-- | @simpleHTTP req@ transmits the 'Request' @req@ by opening a /direct/, non-persistent
Packit acf257
-- connection to the HTTP server that @req@ is destined for, followed by transmitting
Packit acf257
-- it and gathering up the response as a 'Result'. Prior to sending the request,
Packit acf257
-- it is normalized (via 'normalizeRequest'). If you have to mediate the request
Packit acf257
-- via an HTTP proxy, you will have to normalize the request yourself. Or switch to
Packit acf257
-- using 'Network.Browser' instead.
Packit acf257
--
Packit acf257
-- Examples:
Packit acf257
--
Packit acf257
-- > simpleHTTP (getRequest "http://hackage.haskell.org/")
Packit acf257
-- > simpleHTTP (getRequest "http://hackage.haskell.org:8012/")
Packit acf257
Packit acf257
simpleHTTP :: (HStream ty) => Request ty -> IO (Result (Response ty))
Packit acf257
simpleHTTP r = do
Packit acf257
  auth <- getAuth r
Packit acf257
  failHTTPS (rqURI r)
Packit acf257
  c <- openStream (host auth) (fromMaybe 80 (port auth))
Packit acf257
  let norm_r = normalizeRequest defaultNormalizeRequestOptions{normDoClose=True} r
Packit acf257
  simpleHTTP_ c norm_r
Packit acf257
   
Packit acf257
-- | Identical to 'simpleHTTP', but acting on an already opened stream.
Packit acf257
simpleHTTP_ :: HStream ty => HandleStream ty -> Request ty -> IO (Result (Response ty))
Packit acf257
simpleHTTP_ s r = do 
Packit acf257
  let norm_r = normalizeRequest defaultNormalizeRequestOptions{normDoClose=True} r
Packit acf257
  S.sendHTTP s norm_r
Packit acf257
Packit acf257
-- | @sendHTTP hStream httpRequest@ transmits @httpRequest@ (after normalization) over
Packit acf257
-- @hStream@, but does not alter the status of the connection, nor request it to be
Packit acf257
-- closed upon receiving the response.
Packit acf257
sendHTTP :: HStream ty => HandleStream ty -> Request ty -> IO (Result (Response ty))
Packit acf257
sendHTTP conn rq = do
Packit acf257
  let norm_r = normalizeRequest defaultNormalizeRequestOptions rq 
Packit acf257
  S.sendHTTP conn norm_r
Packit acf257
Packit acf257
-- | @sendHTTP_notify hStream httpRequest action@ behaves like 'sendHTTP', but
Packit acf257
-- lets you supply an IO @action@ to execute once the request has been successfully
Packit acf257
-- transmitted over the connection. Useful when you want to set up tracing of
Packit acf257
-- request transmission and its performance.
Packit acf257
sendHTTP_notify :: HStream ty
Packit acf257
                => HandleStream ty
Packit acf257
                -> Request ty
Packit acf257
                -> IO ()
Packit acf257
                -> IO (Result (Response ty))
Packit acf257
sendHTTP_notify conn rq onSendComplete = do
Packit acf257
  let norm_r = normalizeRequest defaultNormalizeRequestOptions rq 
Packit acf257
  S.sendHTTP_notify conn norm_r onSendComplete
Packit acf257
Packit acf257
-- | @receiveHTTP hStream@ reads a 'Request' from the 'HandleStream' @hStream@
Packit acf257
receiveHTTP :: HStream ty => HandleStream ty -> IO (Result (Request ty))
Packit acf257
receiveHTTP conn = S.receiveHTTP conn
Packit acf257
Packit acf257
-- | @respondHTTP hStream httpResponse@ transmits an HTTP 'Response' over
Packit acf257
-- the 'HandleStream' @hStream@. It could be used to implement simple web
Packit acf257
-- server interactions, performing the dual role to 'sendHTTP'.
Packit acf257
respondHTTP :: HStream ty => HandleStream ty -> Response ty -> IO ()
Packit acf257
respondHTTP conn rsp = S.respondHTTP conn rsp
Packit acf257
Packit acf257
Packit acf257
-- | A convenience constructor for a GET 'Request'.
Packit acf257
--
Packit acf257
-- If the URL isn\'t syntactically valid, the function raises an error.
Packit acf257
getRequest
Packit acf257
    :: String             -- ^URL to fetch
Packit acf257
    -> Request_String     -- ^The constructed request
Packit acf257
getRequest urlString = 
Packit acf257
  case parseURI urlString of
Packit acf257
    Nothing -> error ("getRequest: Not a valid URL - " ++ urlString)
Packit acf257
    Just u  -> mkRequest GET u
Packit acf257
Packit acf257
-- | A convenience constructor for a HEAD 'Request'.
Packit acf257
--
Packit acf257
-- If the URL isn\'t syntactically valid, the function raises an error.
Packit acf257
headRequest
Packit acf257
    :: String             -- ^URL to fetch
Packit acf257
    -> Request_String     -- ^The constructed request
Packit acf257
headRequest urlString = 
Packit acf257
  case parseURI urlString of
Packit acf257
    Nothing -> error ("headRequest: Not a valid URL - " ++ urlString)
Packit acf257
    Just u  -> mkRequest HEAD u
Packit acf257
Packit acf257
-- | A convenience constructor for a POST 'Request'.
Packit acf257
--
Packit acf257
-- If the URL isn\'t syntactically valid, the function raises an error.
Packit acf257
postRequest
Packit acf257
    :: String                   -- ^URL to POST to
Packit acf257
    -> Request_String           -- ^The constructed request
Packit acf257
postRequest urlString = 
Packit acf257
  case parseURI urlString of
Packit acf257
    Nothing -> error ("postRequest: Not a valid URL - " ++ urlString)
Packit acf257
    Just u  -> mkRequest POST u
Packit acf257
Packit acf257
-- | A convenience constructor for a POST 'Request'.
Packit acf257
--
Packit acf257
-- It constructs a request and sets the body as well as
Packit acf257
-- the Content-Type and Content-Length headers. The contents of the body
Packit acf257
-- are forced to calculate the value for the Content-Length header.
Packit acf257
--
Packit acf257
-- If the URL isn\'t syntactically valid, the function raises an error.
Packit acf257
postRequestWithBody
Packit acf257
    :: String                      -- ^URL to POST to
Packit acf257
    -> String                      -- ^Content-Type of body
Packit acf257
    -> String                      -- ^The body of the request
Packit acf257
    -> Request_String              -- ^The constructed request
Packit acf257
postRequestWithBody urlString typ body = 
Packit acf257
  case parseURI urlString of
Packit acf257
    Nothing -> error ("postRequestWithBody: Not a valid URL - " ++ urlString)
Packit acf257
    Just u  -> setRequestBody (mkRequest POST u) (typ, body)
Packit acf257
Packit acf257
-- | @getResponseBody response@ takes the response of a HTTP requesting action and
Packit acf257
-- tries to extricate the body of the 'Response' @response@. If the request action
Packit acf257
-- returned an error, an IO exception is raised.
Packit acf257
getResponseBody :: Result (Response ty) -> IO ty
Packit acf257
getResponseBody (Left err) = fail (show err)
Packit acf257
getResponseBody (Right r)  = return (rspBody r)
Packit acf257
Packit acf257
-- | @getResponseBody response@ takes the response of a HTTP requesting action and
Packit acf257
-- tries to extricate the status code of the 'Response' @response@. If the request action
Packit acf257
-- returned an error, an IO exception is raised.
Packit acf257
getResponseCode :: Result (Response ty) -> IO ResponseCode
Packit acf257
getResponseCode (Left err) = fail (show err)
Packit acf257
getResponseCode (Right r)  = return (rspCode r)
Packit acf257
Packit acf257
Packit acf257
--
Packit acf257
-- * TODO
Packit acf257
--     - request pipelining
Packit acf257
--     - https upgrade (includes full TLS, i.e. SSL, implementation)
Packit acf257
--         - use of Stream classes will pay off
Packit acf257
--         - consider C implementation of encryption\/decryption
Packit acf257
--     - comm timeouts
Packit acf257
--     - MIME & entity stuff (happening in separate module)
Packit acf257
--     - support \"*\" uri-request-string for OPTIONS request method
Packit acf257
-- 
Packit acf257
-- 
Packit acf257
-- * Header notes:
Packit acf257
--
Packit acf257
--     [@Host@]
Packit acf257
--                  Required by HTTP\/1.1, if not supplied as part
Packit acf257
--                  of a request a default Host value is extracted
Packit acf257
--                  from the request-uri.
Packit acf257
-- 
Packit acf257
--     [@Connection@] 
Packit acf257
--                  If this header is present in any request or
Packit acf257
--                  response, and it's value is "close", then
Packit acf257
--                  the current request\/response is the last 
Packit acf257
--                  to be allowed on that connection.
Packit acf257
-- 
Packit acf257
--     [@Expect@]
Packit acf257
--                  Should a request contain a body, an Expect
Packit acf257
--                  header will be added to the request.  The added
Packit acf257
--                  header has the value \"100-continue\".  After
Packit acf257
--                  a 417 \"Expectation Failed\" response the request
Packit acf257
--                  is attempted again without this added Expect
Packit acf257
--                  header.
Packit acf257
--                  
Packit acf257
--     [@TransferEncoding,ContentLength,...@]
Packit acf257
--                  if request is inconsistent with any of these
Packit acf257
--                  header values then you may not receive any response
Packit acf257
--                  or will generate an error response (probably 4xx).
Packit acf257
--
Packit acf257
--
Packit acf257
-- * Response code notes
Packit acf257
-- Some response codes induce special behaviour:
Packit acf257
--
Packit acf257
--   [@1xx@]   \"100 Continue\" will cause any unsent request body to be sent.
Packit acf257
--             \"101 Upgrade\" will be returned.
Packit acf257
--             Other 1xx responses are ignored.
Packit acf257
-- 
Packit acf257
--   [@417@]   The reason for this code is \"Expectation failed\", indicating
Packit acf257
--             that the server did not like the Expect \"100-continue\" header
Packit acf257
--             added to a request.  Receipt of 417 will induce another
Packit acf257
--             request attempt (without Expect header), unless no Expect header
Packit acf257
--             had been added (in which case 417 response is returned).