{- | Network.HTTP.Simple

  This module exports the methods 'httpHead' and 'httpGet' and the
  Int value 'redirectDepth'.

  The goal of this module is to provide a very simple interface to http
  head and get functionality utilizing the more detailed functions
  of the Network.HTTP module. There are efforts in place to improve
  Network.HTTP, and if those efforts bear fruit, you should likely seek
  functionality there instead of this module. This module may even be broken
  under a future revision to Network.HTTP. 
  
  Because the goal of this module is to be simple, no attempt at cascading
  various error states to the caller is made at all. If the function fails
  for any reason, Nothing is returned. If you actually want to capture error
  states, you should be using Network.HTTP directly.


  Here is a small complete haskell program illustrating this library:

@
  module Main where
  import Network.URI
  import Network.HTTP
  import Network.HTTP.Simple
  main = do
    let s = \"http:\/\/www.yahoo.com\/\"
    case parseURI s of
      Nothing -> error \"parse uri error\"
      Just uri -> do
           -- first get headers 
           tryHead <- httpHead uri
           case tryHead of
             Nothing -> error \"head error\"
             Just headers -> print headers
           -- now try getting content
           tryGet <- httpGet uri
           case tryGet of
             Nothing -> error \"get error\"
             Just content -> print content
           return ()
@
-}
module Network.HTTP.Simple (httpHead,httpGet,redirectDepth) where
import Data.Char (intToDigit)
import Network.URI
import Network.HTTP

{- 
  License info:

  This module draws heavily on http://darcs.haskell.org/http/test/get.hs,
  which is distributed with the Network.HTTP library
  
  Since the code for Network.HTTP is based on the same BSD3 license as this
  code, I do not believe I am violating the license used by it. I have
  place appropriate references to the original contributors in my own
  license file. please let me know if I have not attributed the original
  authors correctly. It is my intent to honor their licensing wishes.

  The license is a simple BSD3-style license available here:
  
  http://www.b7j0c.org/content/network-http-simple-license.txt

-}

-- | The 'handleEresp' function returns the valid http response code
-- from the simpleHTTP function, or Nothing in the case of a failure.
handleEresp :: Either ConnError a -> Maybe a
handleEresp (Left e) = Nothing
handleEresp (Right v) = Just v

-- | redirectDepth stipulates the number of http redirects we will allow
-- for any given request, defaulted to 10. 
redirectDepth :: Int
redirectDepth = 10

-- | Given a http response Header list, the 'getHeaderVal' function will 
-- find the value for a given field, or return Nothing
getHeaderVal :: HeaderName -> [Header] -> Maybe String
getHeaderVal h (Header k v:hs) = 
    if (h == k) then Just v else getHeaderVal h hs 
getHeaderVal h [] = Nothing

-- | The 'request' function will build a http Request record given 
-- a uri and a method
request :: RequestMethod -> URI -> Request
request method uri = Request{ rqURI = uri,
                              rqMethod = method,
                              rqHeaders = [],
                              rqBody = "" }

-- | The 'httpHead' function will return a list of Headers for a given 
-- request. Should the request fail for any reason, Nothing is returned.
httpHead :: URI -> IO (Maybe [Header])
httpHead uri = do
  eresp <- simpleHTTP (request HEAD uri)
  case (handleEresp eresp) of
    Nothing -> return Nothing
    Just resp -> return (Just (rspHeaders resp))

-- | The 'httpGet' function will return the http response content for a given 
-- request. Should the request fail for any reason, Nothing is returned.
-- This function simply calls the function httpGetN with a seed value of 0
-- to indicate an initial redirect depth level.
httpGet :: URI -> IO (Maybe String)
httpGet uri = httpGetN 0 uri

-- | The httpGetN function attempts to resolve a given uri to an http
-- 200-class response with content. This function will traverse redirects
-- to a depth of 'redirectDepth'. Nothing is returned in the case of any
-- failure or error.
httpGetN :: Int -> URI -> IO (Maybe String)
httpGetN d uri = do
  eresp <- simpleHTTP (request GET uri)
  case (handleEresp eresp) of
    Nothing -> return Nothing -- no response
    Just resp -> case rspCode resp of
        (2,0,0) -> return (Just (rspBody resp)) -- the target content
        (3,0,2) -> do
             case (d >= redirectDepth) of
               True -> return Nothing -- too many redirects
               False -> case getHeaderVal HdrLocation (rspHeaders resp) of
                          Nothing -> return Nothing -- bad redirect headers
                          Just rawRedirect ->
                              case parseURI rawRedirect of
                                Nothing -> return Nothing -- bad uri
                                Just redirectURI -> httpGetN (d+1) redirectURI
        _ -> return Nothing -- unsupported http response