Lucu-0.3.1: HTTP Daemonic LibrarySource codeContentsIndex
Network.HTTP.Lucu.Resource
Contents
Monad
Actions
Getting request header
Finding an entity
Getting a request body
Setting response headers
Writing a response body
Description

This is the Resource Monad; monadic actions to define the behavior of each resources. The Resource Monad is a kind of IO Monad thus it implements Control.Monad.Trans.MonadIO class. It is also a state machine.

Request Processing Flow:

1. A client issues an HTTP request.

2. If the URI of it matches to any resource, the corresponding Resource Monad starts running on a newly spawned thread.

3. The Resource Monad looks at the request header, find (or not find) an entity, receive the request body (if any), decide the response header, and decide the response body. This process will be discussed later.

4. The Resource Monad and its thread stops running. The client may or may not be sending us the next request at this point.

Resource Monad takes the following states. The initial state is Examining Request and the final state is Done.

Examining Request
In this state, a Resource looks at the request header and thinks about an entity for it. If there is a suitable entity, the Resource tells the system an entity tag and its last modification time (foundEntity). If it found no entity, it tells the system so (foundNoEntity). In case it is impossible to decide the existence of entity, which is a typical case for POST requests, Resource does nothing in this state.
Getting Body
A Resource asks the system to receive a request body from client. Before actually reading from the socket, the system sends "100 Continue" to the client if need be. When a Resource transits to the next state without receiving all or part of request body, the system still reads it and just throws it away.
Deciding Header
A Resource makes a decision of status code and response header. When it transits to the next state, the system checks the validness of response header and then write them to the socket.
Deciding Body
In this state, a Resource asks the system to write some response body to the socket. When it transits to the next state without writing any response body, the system completes it depending on the status code.
Done
Everything is over. A Resource can do nothing for the HTTP interaction anymore.

Note that the state transition is one-way: for instance, it is an error to try to read a request body after writing some response. This limitation is for efficiency. We don't want to read the entire request before starting Resource, nor we don't want to postpone writing the entire response till the end of Resource computation.

Synopsis
data Resource a
getConfig :: Resource Config
getRemoteAddr :: Resource SockAddr
getRemoteAddr' :: Resource String
getRemoteHost :: Resource String
getRemoteCertificate :: Resource (Maybe X509)
getRequest :: Resource Request
getMethod :: Resource Method
getRequestURI :: Resource URI
getRequestVersion :: Resource HttpVersion
getResourcePath :: Resource [String]
getPathInfo :: Resource [String]
getQueryForm :: Resource [(String, String)]
getHeader :: ByteString -> Resource (Maybe ByteString)
getAccept :: Resource [MIMEType]
getAcceptEncoding :: Resource [(String, Maybe Double)]
isEncodingAcceptable :: String -> Resource Bool
getContentType :: Resource (Maybe MIMEType)
getAuthorization :: Resource (Maybe AuthCredential)
foundEntity :: ETag -> UTCTime -> Resource ()
foundETag :: ETag -> Resource ()
foundTimeStamp :: UTCTime -> Resource ()
foundNoEntity :: Maybe String -> Resource ()
input :: Int -> Resource String
inputChunk :: Int -> Resource String
inputLBS :: Int -> Resource ByteString
inputChunkLBS :: Int -> Resource ByteString
inputForm :: Int -> Resource [(String, String)]
defaultLimit :: Int
setStatus :: StatusCode -> Resource ()
setHeader :: ByteString -> ByteString -> Resource ()
redirect :: StatusCode -> URI -> Resource ()
setContentType :: MIMEType -> Resource ()
setLocation :: URI -> Resource ()
setContentEncoding :: [String] -> Resource ()
setWWWAuthenticate :: AuthChallenge -> Resource ()
output :: String -> Resource ()
outputChunk :: String -> Resource ()
outputLBS :: ByteString -> Resource ()
outputChunkLBS :: ByteString -> Resource ()
Monad
data Resource a Source
The Resource monad. This monad implements Control.Monad.Trans.MonadIO so it can do any IO actions.
show/hide Instances
Actions
Getting request header
These actions can be computed regardless of the current state, and they don't change the state.
getConfig :: Resource ConfigSource
Get the Config value which is used for the httpd.
getRemoteAddr :: Resource SockAddrSource
Get the SockAddr of the remote host. If you want a string representation instead of SockAddr, use getRemoteAddr'.
getRemoteAddr' :: Resource StringSource
Get the string representation of the address of remote host. If you want a SockAddr instead of String, use getRemoteAddr.
getRemoteHost :: Resource StringSource
Resolve an address to the remote host.
getRemoteCertificate :: Resource (Maybe X509)Source

Return the X.509 certificate of the client, or Nothing if:

  • This request didn't came through an SSL stream.
  • The client didn't send us its certificate.
  • The OpenSSL.Session.VerificationMode of OpenSSL.Session.SSLContext in SSLConfig has not been set to OpenSSL.Session.VerifyPeer.
getRequest :: Resource RequestSource
Get the Request value which represents the request header. In general you don't have to use this action.
getMethod :: Resource MethodSource
Get the Method value of the request.
getRequestURI :: Resource URISource
Get the URI of the request.
getRequestVersion :: Resource HttpVersionSource
Get the HTTP version of the request.
getResourcePath :: Resource [String]Source

Get the path of this Resource (to be exact, Network.HTTP.Lucu.Resource.Tree.ResourceDef) in the Network.HTTP.Lucu.Resource.Tree.ResTree. The result of this action is the exact path in the tree even if the Network.HTTP.Lucu.Resource.Tree.ResourceDef is greedy.

Example:

 main = let tree = mkResTree [ (["foo"], resFoo) ]
        in runHttpd defaultConfig tree

 resFoo = ResourceDef {
     resIsGreedy = True
   , resGet = Just $ do requestURI   <- getRequestURI
                        resourcePath <- getResourcePath
                        pathInfo     <- getPathInfo
                        -- uriPath requestURI == "/foo/bar/baz"
                        -- resourcePath       == ["foo"]
                        -- pathInfo           == ["bar", "baz"]
                        ...
   , ...
   }
getPathInfo :: Resource [String]Source
This is an analogy of CGI PATH_INFO. Its result is always [] if the Network.HTTP.Lucu.Resource.Tree.ResourceDef is not greedy. See getResourcePath.
getQueryForm :: Resource [(String, String)]Source
Assume the query part of request URI as application/x-www-form-urlencoded, and parse it. This action doesn't parse the request body. See inputForm.
getHeader :: ByteString -> Resource (Maybe ByteString)Source
Get a value of given request header. Comparison of header name is case-insensitive. Note that this action is not intended to be used so frequently: there should be actions like getContentType for every common headers.
getAccept :: Resource [MIMEType]Source
Get a list of MIMEType enumerated on header "Accept".
getAcceptEncoding :: Resource [(String, Maybe Double)]Source
Get a list of (contentCoding, qvalue) enumerated on header "Accept-Encoding". The list is sorted in descending order by qvalue.
isEncodingAcceptable :: String -> Resource BoolSource
Check whether a given content-coding is acceptable.
getContentType :: Resource (Maybe MIMEType)Source
Get the header "Content-Type" as MIMEType.
getAuthorization :: Resource (Maybe AuthCredential)Source
Get the header "Authorization" as AuthCredential.
Finding an entity
These actions can be computed only in the Examining Request state. After the computation, the Resource transits to Getting Body state.
foundEntity :: ETag -> UTCTime -> Resource ()Source

Tell the system that the Resource found an entity for the request URI. If this is a GET or HEAD request, a found entity means a datum to be replied. If this is a PUT or DELETE request, it means a datum which was stored for the URI up to now. It is an error to compute foundEntity if this is a POST request.

Computation of foundEntity performs "If-Match" test or "If-None-Match" test if possible. When those tests fail, the computation of Resource immediately aborts with status "412 Precondition Failed" or "304 Not Modified" depending on the situation.

If this is a GET or HEAD request, foundEntity automatically puts "ETag" and "Last-Modified" headers into the response.

foundETag :: ETag -> Resource ()Source

Tell the system that the Resource found an entity for the request URI. The only difference from foundEntity is that foundETag doesn't (and can't) put "Last-Modified" header into the response.

This action is not preferred. You should use foundEntity whenever possible.

foundTimeStamp :: UTCTime -> Resource ()Source

Tell the system that the Resource found an entity for the request URI. The only difference from foundEntity is that foundTimeStamp performs "If-Modified-Since" test or "If-Unmodified-Since" test instead of "If-Match" test or "If-None-Match" test. Be aware that any tests based on last modification time are unsafe because it is possible to mess up such tests by modifying the entity twice in a second.

This action is not preferred. You should use foundEntity whenever possible.

foundNoEntity :: Maybe String -> Resource ()Source

Computation of foundNoEntity mStr tells the system that the Resource found no entity for the request URI. mStr is an optional error message to be replied to the client.

If this is a PUT request, foundNoEntity performs "If-Match" test and aborts with status "412 Precondition Failed" when it failed. If this is a GET, HEAD, POST or DELETE request, foundNoEntity always aborts with status "404 Not Found".

Getting a request body
Computation of these actions changes the state to /Getting Body/.
input :: Int -> Resource StringSource

Computation of input limit attempts to read the request body up to limit bytes, and then make the Resource transit to Deciding Header state. When the actual size of body is larger than limit bytes, computation of Resource immediately aborts with status "413 Request Entity Too Large". When the request has no body, input returns an empty string.

limit may be less than or equal to zero. In this case, the default limitation value (cnfMaxEntityLength) is used. See defaultLimit.

Note that inputLBS is more efficient than input so you should use it whenever possible.

inputChunk :: Int -> Resource StringSource

Computation of inputChunk limit attempts to read a part of request body up to limit bytes. You can read any large request by repeating computation of this action. When you've read all the request body, inputChunk returns an empty string and then make the Resource transit to Deciding Header state.

limit may be less than or equal to zero. In this case, the default limitation value (cnfMaxEntityLength) is used. See defaultLimit.

Note that inputChunkLBS is more efficient than inputChunk so you should use it whenever possible.

inputLBS :: Int -> Resource ByteStringSource
This is mostly the same as input but is more efficient. inputLBS returns a Data.ByteString.Lazy.ByteString but it's not really lazy: reading from the socket just happens at the computation of inputLBS, not at the evaluation of the Data.ByteString.Lazy.ByteString. The same goes for inputChunkLBS.
inputChunkLBS :: Int -> Resource ByteStringSource
This is mostly the same as inputChunk but is more efficient. See inputLBS.
inputForm :: Int -> Resource [(String, String)]Source
Computation of inputForm limit attempts to read the request body with input and parse it as application/x-www-form-urlencoded or multipart/form-data. If the request header "Content-Type" is neither of them, inputForm makes Resource abort with status "415 Unsupported Media Type". If the request has no "Content-Type", it aborts with "400 Bad Request".
defaultLimit :: IntSource
This is just a constant -1. It's better to say input defaultLimit than to say input (-1) but these are exactly the same.
Setting response headers
Computation of these actions changes the state to /Deciding Header/.
setStatus :: StatusCode -> Resource ()Source
Set the response status code. If you omit to compute this action, the status code will be defaulted to "200 OK".
setHeader :: ByteString -> ByteString -> Resource ()Source

Set a value of given resource header. Comparison of header name is case-insensitive. Note that this action is not intended to be used so frequently: there should be actions like setContentType for every common headers.

Some important headers (especially "Content-Length" and "Transfer-Encoding") may be silently dropped or overwritten by the system not to corrupt the interaction with client at the viewpoint of HTTP protocol layer. For instance, if we are keeping the connection alive, without this process it causes a catastrophe to send a header "Content-Length: 10" and actually send a body of 20 bytes long. In this case the client shall only accept the first 10 bytes of response body and thinks that the residual 10 bytes is a part of header of the next response.

redirect :: StatusCode -> URI -> Resource ()Source
Computation of redirect code uri sets the response status to code and "Location" header to uri. The code must satisfy isRedirection or it causes an error.
setContentType :: MIMEType -> Resource ()Source
Computation of setContentType mType sets the response header "Content-Type" to mType.
setLocation :: URI -> Resource ()Source
Computation of setLocation uri sets the response header "Location" to uri.
setContentEncoding :: [String] -> Resource ()Source
Computation of setContentEncoding codings sets the response header "Content-Encoding" to codings.
setWWWAuthenticate :: AuthChallenge -> Resource ()Source
Computation of setWWWAuthenticate challenge sets the response header "WWW-Authenticate" to challenge.
Writing a response body
Computation of these actions changes the state to /Deciding Body/.
output :: String -> Resource ()Source

Computation of output str writes str as a response body, and then make the Resource transit to Done state. It is safe to apply output to an infinite string, such as a lazy stream of /dev/random.

Note that outputLBS is more efficient than output so you should use it whenever possible.

outputChunk :: String -> Resource ()Source

Computation of outputChunk str writes str as a part of response body. You can compute this action multiple times to write a body little at a time. It is safe to apply outputChunk to an infinite string.

Note that outputChunkLBS is more efficient than outputChunk so you should use it whenever possible.

outputLBS :: ByteString -> Resource ()Source
This is mostly the same as output but is more efficient.
outputChunkLBS :: ByteString -> Resource ()Source
This is mostly the same as outputChunk but is more efficient.
Produced by Haddock version 2.4.2