module Network.HTTP.Proxy.Server (proxyMain
,Settings (..)
,Cache (..)
,Default(..)) where
import Network.HTTP hiding (port)
import Network.HTTP.Server hiding (Response, Request)
import Network.HTTP.Server.Logger
import Data.Default.Class
import Network.HostName
import Control.Monad.Reader
type Proxy s a = ReaderT (Settings s) IO a
type ProxyResponse s = Proxy s (Response s)
proxyMain :: forall s. HStream s => Settings s -> IO ()
proxyMain settings = (`runReaderT` settings) $
do mhname <- asks hostname
hname <- case mhname of
Nothing -> lift getHostName
Just hostn -> return hostn
log <- asks logger
port <- asks portnum
let config = defaultConfig {srvPort = fromInteger port
,srvHost = hname
,srvLog = log}
myLogInfo $ "Proxy server started on port " ++ (show port)
lift $ serverWith config (proxyHandler settings)
myLogInfo :: String -> Proxy s ()
myLogInfo s = asks logger >>= \l -> lift (logInfo l 0 s)
myLogWarning :: String -> Proxy s ()
myLogWarning s = asks logger >>= \l -> lift (logWarning l s)
myLogError :: String -> Proxy s ()
myLogError s = asks logger >>= \l -> lift (logError l s)
proxyHandler :: HStream s => Settings s -> Handler s
proxyHandler settings _ _ request = (`runReaderT` settings) $ do
myLogInfo "Checking request authorization"
authorized <- lift $ isAuthorized settings request
if authorized then processRequest settings request
else do myLogWarning $ "Rejecting an unauthorized request: "
++ (show request)
errorProxyUnauthorized
processRequest :: HStream s => Settings s -> Request s -> ProxyResponse s
processRequest settings request = do
myLogInfo "Modifying the request"
modRequest <- lift $ requestModifier settings request
myLogInfo "Querying cache"
mCachedResponse <- lift $ queryCache (cache settings) modRequest
case mCachedResponse of
Just response -> do
myLogInfo "Cache hit: returning cached response"
return response
Nothing -> do
myLogInfo "Cache miss: forwarding the request"
response <- fetch modRequest
myLogInfo "Modifying the response"
modResponse <- lift $ responseModifier settings request response
myLogInfo "Caching the modified response"
lift $ recordInCache (cache settings) request modResponse
return modResponse
fetch :: HStream s => Request s -> ProxyResponse s
fetch request = do
result <- lift $ simpleHTTP request
case result of
Left err -> do myLogError $
"Connection error while fetching an external resource: "
++ show err
lift errorInternalServerError
Right rsp -> return rsp
data Settings s =
Settings {requestModifier :: Request s -> IO (Request s)
,responseModifier :: Request s -> Response s -> IO (Response s)
,cache :: Cache s
,isAuthorized :: Request s -> IO Bool
,logger :: Logger
,portnum :: Integer
,hostname :: Maybe String
}
instance Default (Settings s) where
def = Settings {requestModifier = return
,responseModifier = \_ -> return
,cache = def
,isAuthorized = return . const True
,logger = stdLogger
,portnum = 3128
,hostname = Nothing}
data Cache s = Cache {queryCache :: Request s -> IO (Maybe (Response s))
,recordInCache :: Request s -> Response s -> IO ()
}
instance Default (Cache s) where
def = Cache {queryCache = return . const Nothing
,recordInCache = \_ -> return . const ()}
errorInternalServerError :: HStream s => IO (Response s)
errorInternalServerError = return $ err_response InternalServerError
errorProxyUnauthorized :: HStream s => ProxyResponse s
errorProxyUnauthorized = return $ err_response ProxyAuthenticationRequired
errorBadRequest :: HStream s => IO (Response s)
errorBadRequest = return $ err_response BadRequest