It's not a replacement for Apache nor lighttpd. It is intended
to be used to build an efficient web-based RESTful application
which runs behind a reverse-proxy so it doesn't have some
- functionalities like logging, client filtering or such like.
+ functionalities like logging, client filtering and such.
Version: 1.0
License: PublicDomain
-- Socket Layer.
--
-- Lucu is not a replacement for Apache or lighttpd. It is intended to
--- be used to build an efficient web-based RESTful application. It is
--- also intended to be run behind a reverse-proxy so it doesn't have
--- the following (otherwise essential) functionalities:
+-- be used to build an efficient web-based RESTful application which
+-- runs behind a reverse-proxy so it doesn't have the following
+-- (otherwise essential) functionalities:
--
-- [/Logging/] Lucu doesn't write logs of any requests from any
-- clients.
-- *** Status Code
, StatusCode(..)
- -- *** Abortion
- , Abortion
- , mkAbortion
- , mkAbortion'
- , abort
+ -- *** 'Abortion'
+ , module Network.HTTP.Lucu.Abortion
-- *** ETag
, ETag(..)
OverloadedStrings
, UnicodeSyntax
#-}
--- |Manipulation of WWW authentication.
+-- |HTTP Authentication
module Network.HTTP.Lucu.Authentication
( AuthChallenge(..)
, AuthCredential(..)
, authCredentialP
)
where
+import Control.Monad
import Data.Ascii (Ascii)
import qualified Data.Ascii as A
import Data.Attoparsec.Char8
import Network.HTTP.Lucu.Utils
import Prelude.Unicode
--- |Authorization challenge to be sent to client with
--- \"WWW-Authenticate\" header. See
+-- |Authentication challenge to be sent to clients with
+-- \"WWW-Authenticate\" header field. See
-- 'Network.HTTP.Lucu.Resource.setWWWAuthenticate'.
data AuthChallenge
= BasicAuthChallenge !Realm
deriving (Eq)
--- |'Realm' is just a string which must not contain any non-ASCII letters.
+-- |'Realm' is just an 'Ascii' string.
type Realm = Ascii
-- |Authorization credential to be sent by client with
= BasicAuthCredential !UserID !Password
deriving (Show, Eq)
--- |'UserID' is just a string which must not contain colon and any
--- non-ASCII letters.
-type UserID = Ascii
+-- |'UserID' is just an 'Ascii' string containing no colons (\':\').
+type UserID = Ascii
--- |'Password' is just a string which must not contain any non-ASCII
--- letters.
+-- |'Password' is just an 'Ascii' string.
type Password = Ascii
-- |Convert an 'AuthChallenge' to 'Ascii'.
= A.fromAsciiBuilder $
A.toAsciiBuilder "Basic realm=" ⊕ quoteStr realm
+-- |'Parser' for an 'AuthCredential'.
authCredentialP ∷ Parser AuthCredential
authCredentialP
- = do _ ← string "Basic"
+ = do void $ string "Basic"
skipMany1 lws
b64 ← takeWhile1 base64
case C8.break (≡ ':') (B64.decodeLenient b64) of
OverloadedStrings
, UnicodeSyntax
#-}
--- |Configurations for the Lucu httpd like a port to listen.
+-- |Configurations for the Lucu httpd.
module Network.HTTP.Lucu.Config
( Config(..)
, SSLConfig(..)
import OpenSSL.Session
import System.IO.Unsafe
--- |Configuration record for the Lucu httpd. You need to use
--- 'defaultConfig' or setup your own configuration to run the httpd.
+-- |Configuration record for to run the httpd.
data Config = Config {
- -- |A string which will be sent to clients as \"Server\" field.
+ -- |A banner string to be sent to clients with \"Server\" response
+ -- header field.
cnfServerSoftware ∷ !Ascii
-- |The host name of the server. This value will be used in
-- built-in pages like \"404 Not Found\".
, cnfServerHost ∷ !Text
- -- |A port number (or service name) to listen to HTTP clients.
+ -- |A port number (or a service name) to listen to HTTP clients.
, cnfServerPort ∷ !ServiceName
-- |Local IPv4 address to listen to both HTTP and HTTPS
-- |Local IPv6 address to listen to both HTTP and HTTPS
-- clients. Set this to @('Just' "::")@ if you want to accept any
-- IPv6 connections. Set this to 'Nothing' to disable IPv6. Note
- -- that there is currently no way to assign separate ports to IPv4
- -- and IPv6 server sockets.
+ -- that there is currently no ways to assign separate ports to
+ -- IPv4 and IPv6 server sockets (but I don't think that will be a
+ -- problem.)
, cnfServerV6Addr ∷ !(Maybe HostName)
-- |Configuration for HTTPS connections. Set this 'Nothing' to
-- disable HTTPS.
, cnfSSLConfig ∷ !(Maybe SSLConfig)
- -- |The maximum number of requests to accept in one connection
- -- simultaneously. If a client exceeds this limitation, its last
+ -- |The maximum number of requests to simultaneously accept in one
+ -- connection. If a client exceeds this limitation, its last
-- request won't be processed until a response for its earliest
-- pending request is sent back to the client.
, cnfMaxPipelineDepth ∷ !Int
- -- |The maximum length of request entity to accept in bytes. Note
- -- that this is nothing but a default value which is used when
- -- 'Network.HTTP.Lucu.Resource.getForm' and such like are applied
- -- to 'Network.HTTP.Lucu.Resource.defaultLimit', so there is no
- -- guarantee that this value always constrains all the requests.
+ -- |The maximum length of request entity to accept in octets. Note
+ -- that this is nothing but a default value used by
+ -- 'Network.HTTP.Lucu.Resource.getForm' and such when they are
+ -- applied to 'Network.HTTP.Lucu.Resource.defaultLimit', so there
+ -- is no guarantee that this value always constrains all the
+ -- requests.
, cnfMaxEntityLength ∷ !Int
- -- | Whether to dump too late abortion to the stderr or not. See
+ -- |Whether to dump too late abortions to the stderr or not. See
-- 'Network.HTTP.Lucu.Abortion.abort'.
, cnfDumpTooLateAbortionToStderr ∷ !Bool
- -- |A mapping from extension to MIME Type. This value is used by
- -- 'Network.HTTP.Lucu.StaticFile.staticFile' to guess the MIME
- -- Type of static files. Note that MIME Types are currently
- -- guessed only by file name.
+ -- |A mapping table from file extensions to MIME Types. This value
+ -- is used by 'Network.HTTP.Lucu.StaticFile.staticFile' to guess
+ -- the MIME Type of static files. Note that MIME Types are
+ -- currently guessed only by file name.
--
- -- Guessing by file magic is indeed a wonderful idea but that is
- -- not implemented (yet). But, don't you think it's better a file
- -- system got a MIME Type as a part of inode? Or it might be a
- -- good idea to use GnomeVFS
- -- (<http://developer.gnome.org/doc/API/2.0/gnome-vfs-2.0/>)
- -- instead of vanilla FS.
+ -- Guessing by file magic might be a good idea but that's not
+ -- implemented (yet).
, cnfExtToMIMEType ∷ !ExtMap
}
-- |Configuration record for HTTPS connections.
data SSLConfig
= SSLConfig {
- -- |A port ID to listen to HTTPS clients. Local addresses
- -- (both for IPv4 and IPv6) will be derived from the parent
- -- 'Config'.
+ -- |A port number (or a service name) to listen to HTTPS
+ -- clients. Local addresses (both for IPv4 and IPv6) will be
+ -- derived from the parent 'Config'.
sslServerPort ∷ !ServiceName
- -- |An SSL context for accepting connections.
- , sslContext ∷ !SSLContext
+ -- |An SSL context for accepting connections. You must set it
+ -- up yourself with at least a server certification.
+ , sslContext ∷ !SSLContext
}
-- |The default configuration. Generally you can use this value as-is,
OverloadedStrings
, UnicodeSyntax
#-}
--- |Manipulation of entity tags.
+-- |Entity tags
module Network.HTTP.Lucu.ETag
( ETag(..)
, parseETag
import Network.HTTP.Lucu.Utils
import Prelude.Unicode
--- |An entity tag is made of a weakness flag and a opaque string.
+-- |An entity tag consists of a weakness flag and an opaque string.
data ETag = ETag {
-- |The weakness flag. Weak tags looks like W\/\"blahblah\" and
- -- strong tags are like \"blahblah\".
+ -- strong tags are like \"blahblah\". See:
+ -- <http://www.w3.org/Protocols/rfc2616/rfc2616-sec13.html#sec13.3.3>
etagIsWeak ∷ !Bool
-- |An opaque string. Only characters from 0x20 (sp) to 0x7e (~)
-- are allowed.
, etagToken ∷ !Ascii
} deriving (Eq, Show)
--- |Convert an 'ETag' to 'AsciiBuilder'.
+-- |Convert an 'ETag' to an 'AsciiBuilder'.
printETag ∷ ETag → AsciiBuilder
{-# INLINEABLE printETag #-}
printETag et
endOfInput
return et
--- |This is equivalent to @'ETag' 'Prelude.False'@. If you want to
--- generate an ETag from a file, try using
+-- |This is equivalent to @'ETag' 'False'@. If you want to generate an
+-- ETag from a file, try using
-- 'Network.HTTP.Lucu.StaticFile.generateETagFromFile'.
strongETag ∷ Ascii → ETag
{-# INLINE strongETag #-}
strongETag = ETag False
--- |This is equivalent to @'ETag' 'Prelude.True'@.
+-- |This is equivalent to @'ETag' 'True'@.
weakETag ∷ Ascii → ETag
{-# INLINE weakETag #-}
weakETag = ETag True
+-- |'Parser' for an 'ETag'.
eTagP ∷ Parser ETag
{-# INLINEABLE eTagP #-}
eTagP = do isWeak ← option False (string "W/" *> return True)
str ← quotedStr
return $ ETag isWeak str
+-- |'Parser' for a list of 'ETag's.
eTagListP ∷ Parser [ETag]
{-# INLINEABLE eTagListP #-}
eTagListP = do xs ← listOf eTagP
OverloadedStrings
, UnicodeSyntax
#-}
--- |Manipulation of HTTP version string.
+-- |HTTP version number
module Network.HTTP.Lucu.HttpVersion
( HttpVersion(..)
- , httpVersionP
, printHttpVersion
+
+ , httpVersionP
)
where
import qualified Blaze.Text.Int as BT
import Data.Monoid.Unicode
import Prelude hiding (min)
--- |@'HttpVersion' major minor@ represents \"HTTP\/major.minor\".
+-- |An HTTP version consists of major and minor versions.
data HttpVersion
= HttpVersion !Int !Int
deriving (Eq, Show)
| minA < minB = LT
| otherwise = EQ
-httpVersionP ∷ Parser HttpVersion
-httpVersionP = string "HTTP/"
- *>
- choice [ string "1.1" *> pure (HttpVersion 1 1)
- , string "1.0" *> pure (HttpVersion 1 0)
- , HttpVersion <$> decimal ⊛ (char '.' *> decimal)
- ]
-
-- |Convert an 'HttpVersion' to 'AsciiBuilder'.
printHttpVersion ∷ HttpVersion → AsciiBuilder
printHttpVersion v
= case v of
- -- 頻出するので高速化
+ -- Optimisation for special cases.
HttpVersion 1 0 → A.toAsciiBuilder "HTTP/1.0"
HttpVersion 1 1 → A.toAsciiBuilder "HTTP/1.1"
- -- 一般の場合
+ -- General cases.
HttpVersion maj min
→ A.toAsciiBuilder "HTTP/" ⊕
A.unsafeFromBuilder (BT.integral maj) ⊕
A.toAsciiBuilder "." ⊕
A.unsafeFromBuilder (BT.integral min)
+
+-- |'Parser' for an 'HttpVersion'.
+httpVersionP ∷ Parser HttpVersion
+httpVersionP = string "HTTP/"
+ *>
+ choice [ string "1.1" *> pure (HttpVersion 1 1)
+ , string "1.0" *> pure (HttpVersion 1 0)
+ , HttpVersion <$> decimal ⊛ (char '.' *> decimal)
+ ]
, UnicodeSyntax
#-}
--- |Manipulation of MIME Types.
+-- |MIME Types
module Network.HTTP.Lucu.MIMEType
( MIMEType(..)
, mkMIMEType
import Prelude hiding (min)
import Prelude.Unicode
--- |@'MIMEType' \"major\" \"minor\" [(\"name\", \"value\")]@
--- represents \"major\/minor; name=value\".
+-- |@'MIMEType' \"major\" \"minor\" [(\"name\", \"value\"), ...]@
+-- represents \"major\/minor; name=value; ...\".
data MIMEType = MIMEType {
mtMajor ∷ !CIAscii
, mtMinor ∷ !CIAscii
instance Show MIMEType where
show = A.toString ∘ A.fromAsciiBuilder ∘ printMIMEType
--- |Construct a 'MIMEType' without any parameters.
+-- |@'mkMIMEType' major minor@ returns a 'MIMEType' with the given
+-- @major@ and @minor@ types but without any parameters.
mkMIMEType ∷ CIAscii → CIAscii → MIMEType
{-# INLINE mkMIMEType #-}
mkMIMEType maj min
= MIMEType maj min (∅)
--- |Convert a 'MIMEType' to 'AsciiBuilder'.
+-- |Convert a 'MIMEType' to an 'AsciiBuilder'.
printMIMEType ∷ MIMEType → AsciiBuilder
{-# INLINEABLE printMIMEType #-}
printMIMEType (MIMEType maj min params)
endOfInput
return t
+-- |'Parser' for an 'MIMEType'.
mimeTypeP ∷ Parser MIMEType
{-# INLINEABLE mimeTypeP #-}
mimeTypeP = do maj ← A.toCIAscii <$> token
params ← paramsP
return $ MIMEType maj min params
+-- |'Parser' for a list of 'MIMEType's.
mimeTypeListP ∷ Parser [MIMEType]
{-# INLINE mimeTypeListP #-}
mimeTypeListP = listOf mimeTypeP
{-# LANGUAGE
UnicodeSyntax
#-}
--- |MIME Type guessing by a file extension. This is a poor man's way
--- of guessing MIME Types. It is simple and fast.
+-- |Guessing MIME Types by file extensions. It's not always accurate
+-- but simple and fast.
--
-- In general you don't have to use this module directly.
module Network.HTTP.Lucu.MIMEType.Guess
import Prelude.Unicode
import System.FilePath
--- |'Map' from extension to 'MIMEType'.
+-- |A 'Map' from file extensions to 'MIMEType's.
type ExtMap = Map Text MIMEType
--- |Guess the MIME Type of file.
+-- |Guess the MIME Type of a file.
guessTypeByFileName ∷ ExtMap → FilePath → Maybe MIMEType
guessTypeByFileName extMap fpath
= case takeExtension fpath of
--
-- * A definition of module named @moduleName@.
--
--- * @variableName :: 'ExtMap'@ whose content is a serialization of
--- @extMap@.
+-- * @variableName :: 'ExtMap'@ whose content is the serialised
+-- @extMap@.
--
-- The module "Network.HTTP.Lucu.MIMEType.DefaultExtensionMap" is
-- surely generated using this function.
import Data.Sequence.Unicode hiding ((∅))
import Prelude.Unicode
--- |@'isCtl' c@ is 'Prelude.False' iff @0x20 <= c < 0x7F@.
+-- |@'isCtl' c@ returns 'False' iff @0x20 <= c < 0x7F@.
isCtl ∷ Char → Bool
{-# INLINE isCtl #-}
isCtl c
{-# INLINE isText #-}
isText = (¬) ∘ isCtl
--- |@'isSeparator' c@ is 'Prelude.True' iff c is one of HTTP
+-- |@'isSeparator' c@ returns 'True' iff c is one of the HTTP
-- separators.
isSeparator ∷ Char → Bool
{-# INLINE isSeparator #-}
{-# NOINLINE set #-}
set = FS.charClass "()<>@,;:\\\"/[]?={}\x20\x09"
--- |@'isChar' c@ is 'Prelude.True' iff @c <= 0x7f@.
+-- |@'isChar' c@ returns 'True' iff @c <= 0x7f@.
isChar ∷ Char → Bool
{-# INLINE isChar #-}
isChar = (≤ '\x7F')
--- |@'isToken' c@ is equivalent to @not ('isCtl' c || 'isSeparator'
+-- |@'isToken' c@ is equivalent to @not ('isCtl' c '||' 'isSeparator'
-- c)@
isToken ∷ Char → Bool
{-# INLINE isToken #-}
_ ← char ','
skipMany lws
--- |'token' is similar to @'takeWhile1' 'isToken'@
+-- |'token' is almost the same as @'takeWhile1' 'isToken'@
token ∷ Parser Ascii
{-# INLINE token #-}
token = A.unsafeFromByteString <$> takeWhile1 isToken
isSPHT '\x09' = True
isSPHT _ = False
--- |@'separators'@ is similar to @'takeWhile1' 'isSeparator'@.
+-- |@'separators'@ is almost the same as @'takeWhile1' 'isSeparator'@.
separators ∷ Parser Ascii
{-# INLINE separators #-}
separators = A.unsafeFromByteString <$> takeWhile1 isSeparator
return (y:ys)
return $ read (x:xs)
--- |@'atMost' n v@ is like @'P.many' v@ but applies the given action
--- at most @n@ times.
+-- |@'atMost' n v@ is like @'P.many' v@ but accumulates @v@ at most
+-- @n@ times.
atMost ∷ Alternative f ⇒ Int → f a → f [a]
{-# INLINE atMost #-}
atMost 0 _ = pure []
<|>
pure []
-
data CharAccumState
= CharAccumState {
casChunks ∷ !(S.Seq BS.ByteString)
in
str
+-- |@'manyCharsTill' p end@ takes as many characters untill @p@
+-- succeeds.
manyCharsTill ∷ ∀m b. (Monad m, Alternative m)
⇒ m Char
→ m b
#-}
-- |Provide functionalities to encode/decode MIME parameter values in
-- character sets other than US-ASCII. See:
--- http://www.faqs.org/rfcs/rfc2231.html
+-- <http://www.faqs.org/rfcs/rfc2231.html>
+--
+-- You usually don't have to use this module directly.
module Network.HTTP.Lucu.RFC2231
( printParams
, paramsP
import Prelude.Unicode
import System.IO.Unsafe
+-- |Convert parameter values to an 'AsciiBuilder'.
printParams ∷ Map CIAscii Text → AsciiBuilder
printParams params
| M.null params = (∅)
section (InitialEncodedParam {..}) = 0
section ep = epSection ep
+-- |'Parser' for parameter values.
paramsP ∷ Parser (Map CIAscii Text)
paramsP = decodeParams =≪ P.many (try paramP)
import Prelude.Unicode
-- |This is the definition of HTTP request methods, which shouldn't
--- require any description.
+-- require any descriptions.
data Method = OPTIONS
| GET
| HEAD
| ExtensionMethod !Ascii
deriving (Eq, Show)
--- |This is the definition of HTTP reqest.
+-- |This is the definition of an HTTP reqest.
data Request
= Request {
reqMethod ∷ !Method
| m ≡ PUT = True
| otherwise = False
+-- |'Parser' for a 'Request'.
requestP ∷ Parser Request
requestP = do skipMany crlf
(method, uri, version) ← requestLineP
-- /Examining Request/ and the final state is /Done/.
--
-- [/Examining Request/] In this state, a 'Resource' looks at the
--- request header fields and thinks about a corresponding entity for
--- it. If there is a suitable entity, the 'Resource' tells the
+-- request header fields and thinks about the corresponding 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
-- 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 a request body, the system automatically
--- receives and discards it.
+-- discards it.
--
--- [/Deciding Header/] A 'Resource' makes a decision of status code
--- and response header fields. When it transits to the next state,
--- the system validates and completes the response header fields and
+-- [/Deciding Header/] A 'Resource' makes a decision of response
+-- status code and header fields. When it transits to the next
+-- state, the system validates and completes the header fields and
-- then sends them to the client.
--
-- [/Sending Body/] In this state, a 'Resource' asks the system to
, foundETag
, foundTimeStamp
, foundNoEntity
+ , foundNoEntity'
-- * Receiving a request body
-- |These functions make the 'Resource' transit to the /Receiving
, deleteHeader
-- * Sending a response body
- -- |These functions make the 'Resource' transit to the /Sending
- -- Body/ state.
+
+ -- |These functions make the 'Resource' transit to the
+ -- /Sending Body/ state.
, putChunk
, putChunks
, putBuilder
-- |@'getHeader' name@ returns the value of the request header field
-- @name@. Comparison of header name is case-insensitive. Note that
-- this function is not intended to be used so frequently: there
--- should be actions like 'getContentType' for every common headers.
+-- should be functions like 'getContentType' for every common headers.
getHeader ∷ CIAscii → Resource (Maybe Ascii)
getHeader name
= H.getHeader name <$> getRequest
toTuple (AcceptEncoding {..})
= (aeEncoding, aeQValue)
--- |Return 'True' iff a given content-coding is acceptable.
+-- |Return 'True' iff a given content-coding is acceptable by the
+-- client.
isEncodingAcceptable ∷ CIAscii → Resource Bool
isEncodingAcceptable encoding = any doesMatch <$> getAcceptEncoding
where
driftTo ReceivingBody
+-- |'foundNoEntity'' is the same as @'foundNoEntity' 'Nothing'@.
+foundNoEntity' ∷ Resource ()
+{-# INLINE foundNoEntity' #-}
+foundNoEntity' = foundNoEntity Nothing
+
-- |@'getChunks' limit@ attemts to read the entire request body up to
-- @limit@ bytes, and then make the 'Resource' transit to the
-- When the @limit@ is 'Nothing', 'getChunks' uses the default
-- limitation value ('cnfMaxEntityLength') instead.
--
--- 'getChunks' returns a 'Lazy.ByteString' but it's not really lazy:
--- reading from the socket just happens at the computation of
+-- 'getChunks' returns a lazy 'Lazy.ByteString' but it's not really
+-- lazy: reading from the socket just happens at the computation of
-- 'getChunks', not at the evaluation of the 'Lazy.ByteString'.
getChunks ∷ Maybe Int → Resource Lazy.ByteString
getChunks (Just n)
putChunk ∷ Strict.ByteString → Resource ()
putChunk = putBuilder ∘ BB.fromByteString
--- |Write a chunk in 'Lazy.ByteString' to the response body. It is
--- safe to apply this function to an infinitely long
--- 'Lazy.ByteString'.
+-- |Write a chunk in lazy 'Lazy.ByteString' to the response body. It
+-- can be safely applied to an infinitely long 'Lazy.ByteString'.
--
-- Note that you must first declare the response header
-- \"Content-Type\" before applying this function. See
-- resource path. If 'resGet' is Nothing, the system responds
-- \"405 Method Not Allowed\" for GET requests.
--
- -- It also runs for HEAD request if the 'resHead' is Nothing. In
- -- this case 'output' and such like don't actually write a
- -- response body.
+ -- It also runs for HEAD request if the 'resHead' is 'Nothing'. In
+ -- that case 'putChunk' and such don't actually write a response
+ -- body.
, resGet ∷ !(Maybe (Resource ()))
-- |A 'Resource' to be run when a HEAD request comes for the
-- resource path. If 'resHead' is Nothing, the system runs
-- > main = let tree = mkResTree [ (["foo"], resFoo) ]
-- > in runHttpd defaultConfig tree []
-- >
--- > resFoo = ResourceDef {
+-- > resFoo = emptyResource {
-- > resIsGreedy = True
-- > , resGet = Just $ do requestURI <- getRequestURI
-- > resourcePath <- getResourcePath
-- > -- resourcePath == ["foo"]
-- > -- pathInfo == ["bar", "baz"]
-- > ...
--- > , ...
-- > }
getResourcePath ∷ Resource [Strict.ByteString]
getResourcePath = niResourcePath <$> getInteraction
writeTVar niResponseHasCType False
-- |Run a 'Builder' to construct a chunk, and write it to the response
--- body. It is safe to apply this function to a 'Builder' producing an
+-- body. It can be safely applied to a 'Builder' producing an
-- infinitely long stream of octets.
--
-- Note that you must first declare the response header
import Prelude.Unicode
-- |This is the definition of HTTP status code.
--- 'Network.HTTP.Lucu.Resource.setStatus' accepts these named statuses
--- so you don't have to memorize, for instance, that \"Gateway
+-- 'Network.HTTP.Lucu.Resource.setStatus' accepts these named status
+-- codes so you don't have to memorize, for instance, that \"Gateway
-- Timeout\" is 504.
data StatusCode = Continue
| SwitchingProtocols
| InsufficientStorage
deriving (Eq, Show, Typeable)
--- |Convert a 'StatusCode' to 'AsciiBuilder'.
+-- |Convert a 'StatusCode' to an 'AsciiBuilder'.
printStatusCode ∷ StatusCode → AsciiBuilder
{-# INLINEABLE printStatusCode #-}
printStatusCode (statusCode → (# num, msg #))
A.toAsciiBuilder msg
)
+-- |This is the definition of an HTTP response.
data Response = Response {
resVersion ∷ !HttpVersion
, resStatus ∷ !StatusCode
handleStaticFile sendContent path
= do exists ← liftIO $ fileExist path
unless exists
- $ foundNoEntity Nothing
+ foundNoEntity'
readable ← liftIO $ fileAccess path True False False
unless readable