2012-08-06 18:44:41 +04:00
{- # LANGUAGE OverloadedStrings # -}
2013-07-25 17:18:23 +04:00
{- # LANGUAGE RecordWildCards # -}
2012-08-06 18:44:41 +04:00
-- | A light-weight, minimalistic reverse HTTP proxy.
module Keter.Proxy
( reverseProxy
2013-07-25 16:44:23 +04:00
, HostLookup
2013-07-10 10:57:38 +04:00
, TLSConfig ( .. )
2012-08-06 18:44:41 +04:00
) where
2012-08-09 19:12:32 +04:00
import Prelude hiding ( ( ++ ) , FilePath )
2013-06-03 15:15:13 +04:00
import Control.Monad.IO.Class ( liftIO )
2012-08-06 18:44:41 +04:00
import Data.ByteString ( ByteString )
2012-10-21 09:07:26 +04:00
import qualified Data.ByteString as S
2013-07-25 17:18:23 +04:00
import qualified Data.ByteString.Char8 as S8
2013-06-03 15:45:52 +04:00
import Network.HTTP.ReverseProxy ( waiProxyToSettings , wpsSetIpHeader , SetIpHeader ( .. ) , ProxyDest ( ProxyDest ) , WaiProxyResponse ( .. ) )
2013-07-25 17:18:23 +04:00
import Network.Wai.Application.Static ( defaultFileServerSettings , staticApp , ssListing )
import WaiAppStatic.Listing ( defaultListing )
2012-10-21 09:07:26 +04:00
import qualified Network.Wai as Wai
2013-07-25 17:18:23 +04:00
import Network.HTTP.Types ( status301 , status302 , status303 , status307 , status404 , status200 , mkStatus )
2013-07-25 15:18:32 +04:00
import qualified Network.HTTP.ReverseProxy.Rewrite as Rewrite
2013-06-03 15:15:13 +04:00
import Network.HTTP.Conduit ( Manager )
import qualified Network.Wai.Handler.Warp as Warp
import qualified Network.Wai.Handler.WarpTLS as WarpTLS
import Blaze.ByteString.Builder ( copyByteString )
import Data.Monoid ( mappend )
2013-06-03 15:45:52 +04:00
import Data.Default
2013-07-14 16:55:05 +04:00
import Keter.Types
2013-07-25 17:18:23 +04:00
import qualified Data.Vector as V
import Data.Text.Encoding ( encodeUtf8 )
2013-07-25 18:55:45 +04:00
import qualified Filesystem.Path.CurrentOS as F
2012-08-06 18:44:41 +04:00
-- | Mapping from virtual hostname to port number.
2013-07-25 16:44:23 +04:00
type HostLookup = ByteString -> IO ( Maybe ProxyAction )
2012-08-06 18:44:41 +04:00
2013-07-25 18:55:45 +04:00
reverseProxy :: Bool -> Manager -> HostLookup -> ListeningPort -> IO ()
reverseProxy useHeader manager hostLookup listener =
run $ withClient useHeader manager hostLookup
where
warp host port = Warp . defaultSettings
{ Warp . settingsHost = host
, Warp . settingsPort = port
}
run =
case listener of
LPInsecure host port -> Warp . runSettings ( warp host port )
LPSecure host port cert key -> WarpTLS . runTLS
( WarpTLS . tlsSettings ( F . encodeString cert ) ( F . encodeString key ) )
( warp host port )
2012-08-09 19:12:32 +04:00
2013-06-03 15:45:52 +04:00
withClient :: Bool -- ^ use incoming request header for IP address
-> Manager
2013-07-25 16:44:23 +04:00
-> HostLookup
2013-06-03 15:15:13 +04:00
-> Wai . Application
2013-06-03 15:45:52 +04:00
withClient useHeader manager portLookup =
waiProxyToSettings getDest def
{ wpsSetIpHeader =
if useHeader
then SIHFromHeader
else SIHFromSocket
} manager
2012-08-06 18:44:41 +04:00
where
2013-07-25 16:44:23 +04:00
getDest req =
case lookup " host " $ Wai . requestHeaders req of
Nothing -> return $ WPRResponse missingHostResponse
Just host -> processHost req host
processHost req host = do
mport <- liftIO $ portLookup host
2012-10-02 23:57:27 +04:00
case mport of
2013-07-25 16:44:23 +04:00
Nothing -> return $ WPRResponse $ unknownHostResponse host
2013-07-25 17:18:23 +04:00
Just action -> performAction req action
2012-10-21 09:07:26 +04:00
2013-07-25 17:18:23 +04:00
performAction _ ( PAPort port ) =
return $ WPRProxyDest $ ProxyDest " 127.0.0.1 " port
performAction req ( PAStatic StaticFilesConfig { .. } ) =
fmap WPRResponse $ staticApp ( defaultFileServerSettings sfconfigRoot )
{ ssListing =
if sfconfigListings
then Just defaultListing
else Nothing
} req
performAction req ( PARedirect config ) = return $ WPRResponse $ redirectApp config req
performAction req ( PAReverseProxy config ) = fmap WPRResponse $ Rewrite . simpleReverseProxy manager config req
redirectApp :: RedirectConfig -> Wai . Request -> Wai . Response
redirectApp RedirectConfig { .. } req =
V . foldr checkAction noAction redirconfigActions
2012-10-21 09:07:26 +04:00
where
2013-07-25 17:18:23 +04:00
checkAction ( RedirectAction SPAny dest ) _ = sendTo $ mkUrl dest
checkAction ( RedirectAction ( SPSpecific path ) dest ) other
| encodeUtf8 path == Wai . rawPathInfo req = sendTo $ mkUrl dest
| otherwise = other
noAction = Wai . ResponseBuilder
status404
[ ( " Content-Type " , " text/plain " ) ]
( copyByteString " File not found " )
sendTo url = Wai . ResponseBuilder
status
[ ( " Location " , url ) ]
( copyByteString url )
status =
case redirconfigStatus of
301 -> status301
302 -> status302
303 -> status303
307 -> status307
i -> mkStatus i $ S8 . pack $ show i
mkUrl ( RDUrl url ) = encodeUtf8 url
mkUrl ( RDPrefix isSecure host port ) = S . concat
[ if isSecure then " https:// " else " http:// "
, encodeUtf8 host
, if ( isSecure && port == 443 ) || ( not isSecure && port == 80 )
then " "
else S8 . pack $ ':' : show port
2012-10-21 09:07:26 +04:00
, Wai . rawPathInfo req
, Wai . rawQueryString req
]
2012-08-06 18:44:41 +04:00
2013-07-25 16:44:23 +04:00
missingHostResponse :: Wai . Response
missingHostResponse = Wai . ResponseBuilder
status200
[ ( " Content-Type " , " text/html; charset=utf-8 " ) ]
$ copyByteString " <!DOCTYPE html> \ n <html><head><title>Welcome to Keter</title></head><body><h1>Welcome to Keter</h1><p>You did not provide a virtual hostname for this request.</p></body></html> "
unknownHostResponse :: ByteString -> Wai . Response
unknownHostResponse host = Wai . ResponseBuilder
2013-06-03 15:15:13 +04:00
status200
[ ( " Content-Type " , " text/html; charset=utf-8 " ) ]
2013-07-25 16:44:23 +04:00
( copyByteString " <!DOCTYPE html> \ n <html><head><title>Welcome to Keter</title></head><body><h1>Welcome to Keter</h1><p>The hostname you have provided, <code> "
` mappend ` copyByteString host
` mappend ` copyByteString " </code>, is not recognized.</p></body></html> " )