{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Network.Wai.Handler.Warp.Types where
import Control.Exception
import qualified Data.ByteString as S
import Data.IORef (IORef, readIORef, writeIORef, newIORef)
import Data.Typeable (Typeable)
import Data.X509
import Foreign.Ptr (Ptr)
import System.Posix.Types (Fd)
import qualified System.TimeManager as T
import qualified Network.Wai.Handler.Warp.Date as D
import qualified Network.Wai.Handler.Warp.FdCache as F
import qualified Network.Wai.Handler.Warp.FileInfoCache as I
import Network.Wai.Handler.Warp.Imports
type Port = Int
type HeaderValue = ByteString
data InvalidRequest = NotEnoughLines [String]
| BadFirstLine String
| NonHttp
| IncompleteHeaders
| ConnectionClosedByPeer
| OverLargeHeader
| BadProxyHeader String
deriving (Eq, Typeable)
instance Show InvalidRequest where
show (NotEnoughLines xs) = "Warp: Incomplete request headers, received: " ++ show xs
show (BadFirstLine s) = "Warp: Invalid first line of request: " ++ show s
show NonHttp = "Warp: Request line specified a non-HTTP request"
show IncompleteHeaders = "Warp: Request headers did not finish transmission"
show ConnectionClosedByPeer = "Warp: Client closed connection prematurely"
show OverLargeHeader = "Warp: Request headers too large, possible memory attack detected. Closing connection."
show (BadProxyHeader s) = "Warp: Invalid PROXY protocol header: " ++ show s
instance Exception InvalidRequest
newtype ExceptionInsideResponseBody = ExceptionInsideResponseBody SomeException
deriving (Show, Typeable)
instance Exception ExceptionInsideResponseBody
data FileId = FileId {
fileIdPath :: FilePath
, fileIdFd :: Maybe Fd
}
type SendFile = FileId -> Integer -> Integer -> IO () -> [ByteString] -> IO ()
type BufferPool = IORef ByteString
type Buffer = Ptr Word8
type BufSize = Int
type Recv = IO ByteString
type RecvBuf = Buffer -> BufSize -> IO Bool
data Connection = Connection {
connSendMany :: [ByteString] -> IO ()
, connSendAll :: ByteString -> IO ()
, connSendFile :: SendFile
, connClose :: IO ()
, connFree :: IO ()
, connRecv :: Recv
, connRecvBuf :: RecvBuf
, connWriteBuffer :: Buffer
, connBufferSize :: BufSize
, connHTTP2 :: IORef Bool
}
getConnHTTP2 :: Connection -> IO Bool
getConnHTTP2 conn = readIORef (connHTTP2 conn)
setConnHTTP2 :: Connection -> Bool -> IO ()
setConnHTTP2 conn b = writeIORef (connHTTP2 conn) b
data InternalInfo = InternalInfo {
timeoutManager :: T.Manager
, getDate :: IO D.GMTDate
, getFd :: FilePath -> IO (Maybe F.Fd, F.Refresh)
, getFileInfo :: FilePath -> IO I.FileInfo
}
data Source = Source !(IORef ByteString) !(IO ByteString)
mkSource :: IO ByteString -> IO Source
mkSource func = do
ref <- newIORef S.empty
return $! Source ref func
readSource :: Source -> IO ByteString
readSource (Source ref func) = do
bs <- readIORef ref
if S.null bs
then func
else do
writeIORef ref S.empty
return bs
readSource' :: Source -> IO ByteString
readSource' (Source _ func) = func
leftoverSource :: Source -> ByteString -> IO ()
leftoverSource (Source ref _) bs = writeIORef ref bs
readLeftoverSource :: Source -> IO ByteString
readLeftoverSource (Source ref _) = readIORef ref
data Transport = TCP
| TLS {
tlsMajorVersion :: Int
, tlsMinorVersion :: Int
, tlsNegotiatedProtocol :: Maybe ByteString
, tlsChiperID :: Word16
, tlsClientCertificate :: Maybe CertificateChain
}
| QUIC {
quicNegotiatedProtocol :: Maybe ByteString
, quicChiperID :: Word16
, quicClientCertificate :: Maybe CertificateChain
}
isTransportSecure :: Transport -> Bool
isTransportSecure TCP = False
isTransportSecure _ = True
isTransportQUIC :: Transport -> Bool
isTransportQUIC QUIC{} = True
isTransportQUIC _ = False
getTransportClientCertificate :: Transport -> Maybe CertificateChain
getTransportClientCertificate TCP = Nothing
getTransportClientCertificate (TLS _ _ _ _ cc) = cc
getTransportClientCertificate (QUIC _ _ cc) = cc