module Network.Wai.Handler.Warp.Types where
import Control.Exception
import Data.ByteString (ByteString)
import qualified Data.ByteString as S
import Data.IORef (IORef, readIORef, writeIORef, newIORef)
import Data.Typeable (Typeable)
import Data.Word (Word16, Word8)
import Foreign.Ptr (Ptr)
import qualified Network.Wai.Handler.Warp.Date as D
import qualified Network.Wai.Handler.Warp.FdCache as F
import qualified Network.Wai.Handler.Warp.Timeout as T
#ifndef WINDOWS
import System.Posix.Types (Fd)
#endif
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
#ifdef WINDOWS
type Fd = ()
#endif
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 ()
    
    , connRecv        :: Recv
    
    
    , connRecvBuf     :: RecvBuf
    
    , connWriteBuffer :: Buffer
    
    , connBufferSize  :: BufSize
    }
data InternalInfo = InternalInfo {
    threadHandle :: T.Handle
  , timeoutManager :: T.Manager
  , fdCacher :: Maybe F.MutableFdCache
  , dateCacher :: D.DateCache
  }
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
                 }  
isTransportSecure :: Transport -> Bool
isTransportSecure TCP = False
isTransportSecure _   = True