module Network.MoHWS.Server.Request where
import qualified Network.MoHWS.HTTP.Request as Request
import Network.BSD (HostEntry, )
import Network.Socket (HostAddress, PortNumber, )
data T body = Cons
{
T body -> T body
clientRequest :: Request.T body,
T body -> HostAddress
clientAddress :: HostAddress,
T body -> Maybe HostEntry
clientName :: Maybe HostEntry,
T body -> HostEntry
requestHostName :: HostEntry,
T body -> String
serverURIPath :: String,
T body -> String
serverFilename :: FilePath,
T body -> PortNumber
serverPort :: PortNumber
}
deriving Int -> T body -> ShowS
[T body] -> ShowS
T body -> String
(Int -> T body -> ShowS)
-> (T body -> String) -> ([T body] -> ShowS) -> Show (T body)
forall body. Int -> T body -> ShowS
forall body. [T body] -> ShowS
forall body. T body -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [T body] -> ShowS
$cshowList :: forall body. [T body] -> ShowS
show :: T body -> String
$cshow :: forall body. T body -> String
showsPrec :: Int -> T body -> ShowS
$cshowsPrec :: forall body. Int -> T body -> ShowS
Show
instance Functor T where
fmap :: (a -> b) -> T a -> T b
fmap a -> b
f T a
req =
Cons :: forall body.
T body
-> HostAddress
-> Maybe HostEntry
-> HostEntry
-> String
-> String
-> PortNumber
-> T body
Cons {
clientAddress :: HostAddress
clientAddress = T a -> HostAddress
forall body. T body -> HostAddress
clientAddress T a
req,
clientName :: Maybe HostEntry
clientName = T a -> Maybe HostEntry
forall body. T body -> Maybe HostEntry
clientName T a
req,
requestHostName :: HostEntry
requestHostName = T a -> HostEntry
forall body. T body -> HostEntry
requestHostName T a
req,
serverURIPath :: String
serverURIPath = T a -> String
forall body. T body -> String
serverURIPath T a
req,
serverFilename :: String
serverFilename = T a -> String
forall body. T body -> String
serverFilename T a
req,
serverPort :: PortNumber
serverPort = T a -> PortNumber
forall body. T body -> PortNumber
serverPort T a
req,
clientRequest :: T b
clientRequest = (a -> b) -> T a -> T b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (T a -> T b) -> T a -> T b
forall a b. (a -> b) -> a -> b
$ T a -> T a
forall body. T body -> T body
clientRequest T a
req
}