{-# LANGUAGE DeriveDataTypeable #-}
module Network.Wai.Request
( appearsSecure
, guessApproot
, RequestSizeException(..)
, requestSizeCheck
) where
import Control.Exception (Exception, throwIO)
import Data.ByteString (ByteString)
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as C
import Data.IORef (atomicModifyIORef', newIORef)
import Data.Maybe (fromMaybe)
import Data.Typeable (Typeable)
import Data.Word (Word64)
import Network.HTTP.Types (HeaderName)
import Network.Wai
appearsSecure :: Request -> Bool
Request
request = Request -> Bool
isSecure Request
request Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry HeaderName -> (ByteString -> Bool) -> Bool
matchHeader)
[ (HeaderName
"HTTPS" , (forall a. Eq a => a -> a -> Bool
== ByteString
"on"))
, (HeaderName
"HTTP_X_FORWARDED_SSL" , (forall a. Eq a => a -> a -> Bool
== ByteString
"on"))
, (HeaderName
"HTTP_X_FORWARDED_SCHEME", (forall a. Eq a => a -> a -> Bool
== ByteString
"https"))
, (HeaderName
"HTTP_X_FORWARDED_PROTO" , (forall a. Eq a => a -> a -> Bool
== [ByteString
"https"]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
take Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ByteString -> [ByteString]
C.split Char
',')
, (HeaderName
"X-Forwarded-Proto" , (forall a. Eq a => a -> a -> Bool
== ByteString
"https"))
]
where
matchHeader :: HeaderName -> (ByteString -> Bool) -> Bool
matchHeader :: HeaderName -> (ByteString -> Bool) -> Bool
matchHeader HeaderName
h ByteString -> Bool
f = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False ByteString -> Bool
f forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
h forall a b. (a -> b) -> a -> b
$ Request -> RequestHeaders
requestHeaders Request
request
guessApproot :: Request -> ByteString
guessApproot :: Request -> ByteString
guessApproot Request
req =
(if Request -> Bool
appearsSecure Request
req then ByteString
"https://" else ByteString
"http://") ByteString -> ByteString -> ByteString
`S.append`
forall a. a -> Maybe a -> a
fromMaybe ByteString
"localhost" (Request -> Maybe ByteString
requestHeaderHost Request
req)
newtype RequestSizeException
= RequestSizeException Word64
deriving (RequestSizeException -> RequestSizeException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestSizeException -> RequestSizeException -> Bool
$c/= :: RequestSizeException -> RequestSizeException -> Bool
== :: RequestSizeException -> RequestSizeException -> Bool
$c== :: RequestSizeException -> RequestSizeException -> Bool
Eq, Eq RequestSizeException
RequestSizeException -> RequestSizeException -> Bool
RequestSizeException -> RequestSizeException -> Ordering
RequestSizeException
-> RequestSizeException -> RequestSizeException
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 :: RequestSizeException
-> RequestSizeException -> RequestSizeException
$cmin :: RequestSizeException
-> RequestSizeException -> RequestSizeException
max :: RequestSizeException
-> RequestSizeException -> RequestSizeException
$cmax :: RequestSizeException
-> RequestSizeException -> RequestSizeException
>= :: RequestSizeException -> RequestSizeException -> Bool
$c>= :: RequestSizeException -> RequestSizeException -> Bool
> :: RequestSizeException -> RequestSizeException -> Bool
$c> :: RequestSizeException -> RequestSizeException -> Bool
<= :: RequestSizeException -> RequestSizeException -> Bool
$c<= :: RequestSizeException -> RequestSizeException -> Bool
< :: RequestSizeException -> RequestSizeException -> Bool
$c< :: RequestSizeException -> RequestSizeException -> Bool
compare :: RequestSizeException -> RequestSizeException -> Ordering
$ccompare :: RequestSizeException -> RequestSizeException -> Ordering
Ord, Typeable)
instance Exception RequestSizeException
instance Show RequestSizeException where
showsPrec :: Int -> RequestSizeException -> ShowS
showsPrec Int
p (RequestSizeException Word64
limit) =
String -> ShowS
showString String
"Request Body is larger than " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
p Word64
limit forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" bytes."
requestSizeCheck :: Word64 -> Request -> IO Request
requestSizeCheck :: Word64 -> Request -> IO Request
requestSizeCheck Word64
maxSize Request
req =
case Request -> RequestBodyLength
requestBodyLength Request
req of
KnownLength Word64
len ->
if Word64
len forall a. Ord a => a -> a -> Bool
> Word64
maxSize
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Request
req { requestBody :: IO ByteString
requestBody = forall e a. Exception e => e -> IO a
throwIO (Word64 -> RequestSizeException
RequestSizeException Word64
maxSize) }
else forall (m :: * -> *) a. Monad m => a -> m a
return Request
req
RequestBodyLength
ChunkedBody -> do
IORef Word64
currentSize <- forall a. a -> IO (IORef a)
newIORef Word64
0
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Request
req
{ requestBody :: IO ByteString
requestBody = do
ByteString
bs <- Request -> IO ByteString
requestBody Request
req
Word64
total <-
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef Word64
currentSize forall a b. (a -> b) -> a -> b
$ \Word64
sz ->
let nextSize :: Word64
nextSize = Word64
sz forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
S.length ByteString
bs)
in (Word64
nextSize, Word64
nextSize)
if Word64
total forall a. Ord a => a -> a -> Bool
> Word64
maxSize
then forall e a. Exception e => e -> IO a
throwIO (Word64 -> RequestSizeException
RequestSizeException Word64
maxSize)
else forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
bs
}