{-# OPTIONS_HADDOCK not-home #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
-- | Internal constructors and helper functions. Note that no guarantees are
-- given for stability of these interfaces.
module Network.Wai.Internal where

import           Data.ByteString.Builder      (Builder)
import qualified Data.ByteString              as B hiding (pack)
import           Data.Text                    (Text)
import           Data.Typeable                (Typeable)
import           Data.Vault.Lazy              (Vault)
import           Data.Word                    (Word64)
import qualified Network.HTTP.Types           as H
import           Network.Socket               (SockAddr)
import           Data.List                    (intercalate)

-- | Information on the request sent by the client. This abstracts away the
-- details of the underlying implementation.
{-# DEPRECATED requestBody "requestBody's name is misleading because it only gets a partial chunk of the body. Use getRequestBodyChunk instead." #-}
data Request = Request {
  -- | Request method such as GET.
     Request -> Method
requestMethod        :: H.Method
  -- | HTTP version such as 1.1.
  ,  Request -> HttpVersion
httpVersion          :: H.HttpVersion
  -- | Extra path information sent by the client. The meaning varies slightly
  -- depending on backend; in a standalone server setting, this is most likely
  -- all information after the domain name. In a CGI application, this would be
  -- the information following the path to the CGI executable itself.
  --
  -- Middlewares and routing tools should not modify this raw value, as it may
  -- be used for such things as creating redirect destinations by applications.
  -- Instead, if you are writing a middleware or routing framework, modify the
  -- @pathInfo@ instead. This is the approach taken by systems like Yesod
  -- subsites.
  --
  -- /Note/: At the time of writing this documentation, there is at least one
  -- system (@Network.Wai.UrlMap@ from @wai-extra@) that does not follow the
  -- above recommendation. Therefore, it is recommended that you test the
  -- behavior of your application when using @rawPathInfo@ and any form of
  -- library that might modify the @Request@.
  ,  Request -> Method
rawPathInfo          :: B.ByteString
  -- | If no query string was specified, this should be empty. This value
  -- /will/ include the leading question mark.
  -- Do not modify this raw value - modify queryString instead.
  ,  Request -> Method
rawQueryString       :: B.ByteString
  -- | A list of headers (a pair of key and value) in an HTTP request.
  ,  Request -> RequestHeaders
requestHeaders       :: H.RequestHeaders
  -- | Was this request made over an SSL connection?
  --
  -- Note that this value will /not/ tell you if the client originally made
  -- this request over SSL, but rather whether the current connection is SSL.
  -- The distinction lies with reverse proxies. In many cases, the client will
  -- connect to a load balancer over SSL, but connect to the WAI handler
  -- without SSL. In such a case, 'isSecure' will be 'False', but from a user
  -- perspective, there is a secure connection.
  ,  Request -> Bool
isSecure             :: Bool
  -- | The client\'s host information.
  ,  Request -> SockAddr
remoteHost           :: SockAddr
  -- | Path info in individual pieces - the URL without a hostname/port and
  -- without a query string, split on forward slashes.
  ,  Request -> [Text]
pathInfo             :: [Text]
  -- | Parsed query string information.
  ,  Request -> Query
queryString          :: H.Query
  -- | Get the next chunk of the body. Returns 'B.empty' when the
  -- body is fully consumed. Since 3.2.2, this is deprecated in favor of 'getRequestBodyChunk'.
  ,  Request -> IO Method
requestBody          :: IO B.ByteString
  -- | A location for arbitrary data to be shared by applications and middleware.
  ,  Request -> Vault
vault                 :: Vault
  -- | The size of the request body. In the case of a chunked request body,
  -- this may be unknown.
  --
  -- Since 1.4.0
  ,  Request -> RequestBodyLength
requestBodyLength     :: RequestBodyLength
  -- | The value of the Host header in a HTTP request.
  --
  -- Since 2.0.0
  ,  Request -> Maybe Method
requestHeaderHost     :: Maybe B.ByteString
  -- | The value of the Range header in a HTTP request.
  --
  -- Since 2.0.0
  ,  Request -> Maybe Method
requestHeaderRange   :: Maybe B.ByteString
  -- | The value of the Referer header in a HTTP request.
  --
  -- Since 3.2.0
  ,  Request -> Maybe Method
requestHeaderReferer   :: Maybe B.ByteString
  -- | The value of the User-Agent header in a HTTP request.
  --
  -- Since 3.2.0
  ,  Request -> Maybe Method
requestHeaderUserAgent :: Maybe B.ByteString
  }
  deriving (Typeable)

-- | Get the next chunk of the body. Returns 'B.empty' when the
-- body is fully consumed.
--
-- @since 3.2.2
getRequestBodyChunk :: Request -> IO B.ByteString
getRequestBodyChunk :: Request -> IO Method
getRequestBodyChunk = Request -> IO Method
requestBody

instance Show Request where
    show :: Request -> String
show Request{Bool
Query
RequestHeaders
[Text]
Maybe Method
IO Method
Method
HttpVersion
SockAddr
Vault
RequestBodyLength
requestHeaderUserAgent :: Maybe Method
requestHeaderReferer :: Maybe Method
requestHeaderRange :: Maybe Method
requestHeaderHost :: Maybe Method
requestBodyLength :: RequestBodyLength
vault :: Vault
requestBody :: IO Method
queryString :: Query
pathInfo :: [Text]
remoteHost :: SockAddr
isSecure :: Bool
requestHeaders :: RequestHeaders
rawQueryString :: Method
rawPathInfo :: Method
httpVersion :: HttpVersion
requestMethod :: Method
requestHeaderUserAgent :: Request -> Maybe Method
requestHeaderReferer :: Request -> Maybe Method
requestHeaderRange :: Request -> Maybe Method
requestHeaderHost :: Request -> Maybe Method
requestBodyLength :: Request -> RequestBodyLength
vault :: Request -> Vault
requestBody :: Request -> IO Method
queryString :: Request -> Query
pathInfo :: Request -> [Text]
remoteHost :: Request -> SockAddr
isSecure :: Request -> Bool
requestHeaders :: Request -> RequestHeaders
rawQueryString :: Request -> Method
rawPathInfo :: Request -> Method
httpVersion :: Request -> HttpVersion
requestMethod :: Request -> Method
..} = String
"Request {" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
b | (String
a,String
b) <- [(String, String)]
fields] String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"}"
        where
            fields :: [(String, String)]
fields =
                [(String
"requestMethod",Method -> String
forall a. Show a => a -> String
show Method
requestMethod)
                ,(String
"httpVersion",HttpVersion -> String
forall a. Show a => a -> String
show HttpVersion
httpVersion)
                ,(String
"rawPathInfo",Method -> String
forall a. Show a => a -> String
show Method
rawPathInfo)
                ,(String
"rawQueryString",Method -> String
forall a. Show a => a -> String
show Method
rawQueryString)
                ,(String
"requestHeaders",RequestHeaders -> String
forall a. Show a => a -> String
show RequestHeaders
requestHeaders)
                ,(String
"isSecure",Bool -> String
forall a. Show a => a -> String
show Bool
isSecure)
                ,(String
"remoteHost",SockAddr -> String
forall a. Show a => a -> String
show SockAddr
remoteHost)
                ,(String
"pathInfo",[Text] -> String
forall a. Show a => a -> String
show [Text]
pathInfo)
                ,(String
"queryString",Query -> String
forall a. Show a => a -> String
show Query
queryString)
                ,(String
"requestBody",String
"<IO ByteString>")
                ,(String
"vault",String
"<Vault>")
                ,(String
"requestBodyLength",RequestBodyLength -> String
forall a. Show a => a -> String
show RequestBodyLength
requestBodyLength)
                ,(String
"requestHeaderHost",Maybe Method -> String
forall a. Show a => a -> String
show Maybe Method
requestHeaderHost)
                ,(String
"requestHeaderRange",Maybe Method -> String
forall a. Show a => a -> String
show Maybe Method
requestHeaderRange)
                ]


data Response
    = ResponseFile H.Status H.ResponseHeaders FilePath (Maybe FilePart)
    | ResponseBuilder H.Status H.ResponseHeaders Builder
    | ResponseStream H.Status H.ResponseHeaders StreamingBody
    | ResponseRaw (IO B.ByteString -> (B.ByteString -> IO ()) -> IO ()) Response
  deriving Typeable

-- | Represents a streaming HTTP response body. It's a function of two
-- parameters; the first parameter provides a means of sending another chunk of
-- data, and the second parameter provides a means of flushing the data to the
-- client.
--
-- Since 3.0.0
type StreamingBody = (Builder -> IO ()) -> IO () -> IO ()

-- | The size of the request body. In the case of chunked bodies, the size will
-- not be known.
--
-- Since 1.4.0
data RequestBodyLength = ChunkedBody | KnownLength Word64 deriving Int -> RequestBodyLength -> ShowS
[RequestBodyLength] -> ShowS
RequestBodyLength -> String
(Int -> RequestBodyLength -> ShowS)
-> (RequestBodyLength -> String)
-> ([RequestBodyLength] -> ShowS)
-> Show RequestBodyLength
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestBodyLength] -> ShowS
$cshowList :: [RequestBodyLength] -> ShowS
show :: RequestBodyLength -> String
$cshow :: RequestBodyLength -> String
showsPrec :: Int -> RequestBodyLength -> ShowS
$cshowsPrec :: Int -> RequestBodyLength -> ShowS
Show

-- | Information on which part to be sent.
--   Sophisticated application handles Range (and If-Range) then
--   create 'FilePart'.
data FilePart = FilePart
    { FilePart -> Integer
filePartOffset    :: Integer
    , FilePart -> Integer
filePartByteCount :: Integer
    , FilePart -> Integer
filePartFileSize  :: Integer
    } deriving Int -> FilePart -> ShowS
[FilePart] -> ShowS
FilePart -> String
(Int -> FilePart -> ShowS)
-> (FilePart -> String) -> ([FilePart] -> ShowS) -> Show FilePart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilePart] -> ShowS
$cshowList :: [FilePart] -> ShowS
show :: FilePart -> String
$cshow :: FilePart -> String
showsPrec :: Int -> FilePart -> ShowS
$cshowsPrec :: Int -> FilePart -> ShowS
Show

-- | A special datatype to indicate that the WAI handler has received the
-- response. This is to avoid the need for Rank2Types in the definition of
-- Application.
--
-- It is /highly/ advised that only WAI handlers import and use the data
-- constructor for this data type.
--
-- Since 3.0.0
data ResponseReceived = ResponseReceived
    deriving Typeable