{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Snap.Util.Proxy
( ProxyType(..)
, behindProxy
) where
import Control.Applicative (Alternative ((<|>)))
import Control.Monad (mfilter)
import qualified Data.ByteString.Char8 as S (breakEnd, dropWhile, null, readInt, spanEnd)
import Data.Char (isSpace)
import Data.Maybe (fromMaybe)
import Snap.Core (MonadSnap, Request (rqClientAddr, rqClientPort), getHeader, modifyRequest)
data ProxyType = NoProxy
| X_Forwarded_For
deriving (ReadPrec [ProxyType]
ReadPrec ProxyType
Int -> ReadS ProxyType
ReadS [ProxyType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ProxyType]
$creadListPrec :: ReadPrec [ProxyType]
readPrec :: ReadPrec ProxyType
$creadPrec :: ReadPrec ProxyType
readList :: ReadS [ProxyType]
$creadList :: ReadS [ProxyType]
readsPrec :: Int -> ReadS ProxyType
$creadsPrec :: Int -> ReadS ProxyType
Read, Int -> ProxyType -> ShowS
[ProxyType] -> ShowS
ProxyType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProxyType] -> ShowS
$cshowList :: [ProxyType] -> ShowS
show :: ProxyType -> String
$cshow :: ProxyType -> String
showsPrec :: Int -> ProxyType -> ShowS
$cshowsPrec :: Int -> ProxyType -> ShowS
Show, ProxyType -> ProxyType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProxyType -> ProxyType -> Bool
$c/= :: ProxyType -> ProxyType -> Bool
== :: ProxyType -> ProxyType -> Bool
$c== :: ProxyType -> ProxyType -> Bool
Eq, Eq ProxyType
ProxyType -> ProxyType -> Bool
ProxyType -> ProxyType -> Ordering
ProxyType -> ProxyType -> ProxyType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ProxyType -> ProxyType -> ProxyType
$cmin :: ProxyType -> ProxyType -> ProxyType
max :: ProxyType -> ProxyType -> ProxyType
$cmax :: ProxyType -> ProxyType -> ProxyType
>= :: ProxyType -> ProxyType -> Bool
$c>= :: ProxyType -> ProxyType -> Bool
> :: ProxyType -> ProxyType -> Bool
$c> :: ProxyType -> ProxyType -> Bool
<= :: ProxyType -> ProxyType -> Bool
$c<= :: ProxyType -> ProxyType -> Bool
< :: ProxyType -> ProxyType -> Bool
$c< :: ProxyType -> ProxyType -> Bool
compare :: ProxyType -> ProxyType -> Ordering
$ccompare :: ProxyType -> ProxyType -> Ordering
Ord)
behindProxy :: MonadSnap m => ProxyType -> m a -> m a
behindProxy :: forall (m :: * -> *) a. MonadSnap m => ProxyType -> m a -> m a
behindProxy ProxyType
NoProxy = forall a. a -> a
id
behindProxy ProxyType
X_Forwarded_For = ((forall (m :: * -> *). MonadSnap m => (Request -> Request) -> m ()
modifyRequest Request -> Request
xForwardedFor) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>)
{-# INLINE behindProxy #-}
xForwardedFor :: Request -> Request
xForwardedFor :: Request -> Request
xForwardedFor Request
req = Request
req { rqClientAddr :: ByteString
rqClientAddr = ByteString
ip
, rqClientPort :: Int
rqClientPort = Int
port
}
where
extract :: ByteString -> ByteString
extract = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> (ByteString, ByteString)
S.spanEnd Char -> Bool
isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> ByteString
S.dropWhile Char -> Bool
isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> (ByteString, ByteString)
S.breakEnd (forall a. Eq a => a -> a -> Bool
== Char
',')
ip :: ByteString
ip = forall a. a -> Maybe a -> a
fromMaybe (Request -> ByteString
rqClientAddr Request
req) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Bool
S.null) forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
extract forall a b. (a -> b) -> a -> b
$
forall a. HasHeaders a => CI ByteString -> a -> Maybe ByteString
getHeader CI ByteString
"Forwarded-For" Request
req forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
forall a. HasHeaders a => CI ByteString -> a -> Maybe ByteString
getHeader CI ByteString
"X-Forwarded-For" Request
req
port :: Int
port = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Request -> Int
rqClientPort Request
req) forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$ (ByteString -> Maybe (Int, ByteString)
S.readInt forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
extract forall a b. (a -> b) -> a -> b
$
forall a. HasHeaders a => CI ByteString -> a -> Maybe ByteString
getHeader CI ByteString
"Forwarded-Port" Request
req forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
forall a. HasHeaders a => CI ByteString -> a -> Maybe ByteString
getHeader CI ByteString
"X-Forwarded-Port" Request
req
{-# INLINE xForwardedFor #-}