Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.Wai.Application.Classic
Description
WAI (Web Application Interface) Application for static files and CGI.
Synopsis
- data ClassicAppSpec = ClassicAppSpec {}
- defaultClassicAppSpec :: ClassicAppSpec
- data StatusInfo
- data FileAppSpec = FileAppSpec {}
- defaultFileAppSpec :: FileAppSpec
- data FileRoute = FileRoute {}
- fileApp :: ClassicAppSpec -> FileAppSpec -> FileRoute -> Application
- data RedirectRoute = RedirectRoute {
- redirectSrc :: Path
- redirectDst :: Path
- redirectApp :: ClassicAppSpec -> RedirectRoute -> Application
- data CgiAppSpec = CgiAppSpec {}
- defaultCgiAppSpec :: CgiAppSpec
- data CgiRoute = CgiRoute {}
- cgiApp :: ClassicAppSpec -> CgiAppSpec -> CgiRoute -> Application
- data RevProxyAppSpec = RevProxyAppSpec {}
- data RevProxyRoute = RevProxyRoute {}
- revProxyApp :: ClassicAppSpec -> RevProxyAppSpec -> RevProxyRoute -> Application
- fromString :: IsString a => String -> a
- isSuffixOf :: Path -> Path -> Bool
- (</>) :: Path -> Path -> Path
- (<.>) :: Path -> Path -> Path
- hasTrailingPathSeparator :: Path -> Bool
- type Path = ByteString
- pathString :: Path -> String
- (<\>) :: Path -> Path -> Path
- breakAtSeparator :: Path -> (Path, Path)
- hasLeadingPathSeparator :: Path -> Bool
- redirectHeader :: Request -> ResponseHeaders
- hostPort :: Request -> (ByteString, ByteString)
Common
data ClassicAppSpec Source #
Constructors
ClassicAppSpec | |
Fields
|
defaultClassicAppSpec :: ClassicAppSpec Source #
Default value for ClassicAppSpec
. softwareName
is "Classic". dater
calls epochTime
for every request. statusFileDir
is "/usr/local/share/html/status/".
data StatusInfo Source #
Constructors
StatusByteString ByteString | HTTP status body is created from |
StatusFile Path Integer | HTTP status body is created from |
StatusNone | No HTTP status body. |
Instances
Show StatusInfo Source # | |
Defined in Network.Wai.Application.Classic.Types Methods showsPrec :: Int -> StatusInfo -> ShowS # show :: StatusInfo -> String # showList :: [StatusInfo] -> ShowS # | |
Eq StatusInfo Source # | |
Defined in Network.Wai.Application.Classic.Types |
Files
data FileAppSpec Source #
defaultFileAppSpec :: FileAppSpec Source #
Default value for defaultFileAppSpec
. indexFile
is "index.html". isHTML
matches "*.html" and "*.html".
fileApp :: ClassicAppSpec -> FileAppSpec -> FileRoute -> Application Source #
Handle GET and HEAD for a static file.
If pathInfo
ends with '/', indexFile
is automatically
added. In this case, "Acceptable-Language:" is also handled. Suppose
indexFile
is "index.html" and if the value is "ja,en", then
"index.html.ja", "index.html.en", and "index.html" are tried to be
opened in order.
If pathInfo
does not end with '/' and a corresponding index file
exist, redirection is specified in HTTP response.
Directory contents are NOT automatically listed. To list directory contents, an index file must be created beforehand.
The following HTTP headers are handled: Acceptable-Language:, If-Modified-Since:, Range:, If-Range:, If-Unmodified-Since:.
Redirect
data RedirectRoute Source #
Constructors
RedirectRoute | |
Fields
|
Instances
Show RedirectRoute Source # | |
Defined in Network.Wai.Application.Classic.Types Methods showsPrec :: Int -> RedirectRoute -> ShowS # show :: RedirectRoute -> String # showList :: [RedirectRoute] -> ShowS # | |
Eq RedirectRoute Source # | |
Defined in Network.Wai.Application.Classic.Types Methods (==) :: RedirectRoute -> RedirectRoute -> Bool # (/=) :: RedirectRoute -> RedirectRoute -> Bool # |
redirectApp :: ClassicAppSpec -> RedirectRoute -> Application Source #
CGI
data CgiAppSpec Source #
Constructors
CgiAppSpec | |
Instances
Show CgiAppSpec Source # | |
Defined in Network.Wai.Application.Classic.Types Methods showsPrec :: Int -> CgiAppSpec -> ShowS # show :: CgiAppSpec -> String # showList :: [CgiAppSpec] -> ShowS # | |
Eq CgiAppSpec Source # | |
Defined in Network.Wai.Application.Classic.Types |
defaultCgiAppSpec :: CgiAppSpec Source #
Default value for defaultCgiAppSpec
. indexCgi
is "index.cgi".
cgiApp :: ClassicAppSpec -> CgiAppSpec -> CgiRoute -> Application Source #
Handle GET and POST for CGI.
The program to link this library must ignore SIGCHLD as follows:
installHandler sigCHLD Ignore Nothing
Reverse Proxy
data RevProxyAppSpec Source #
Constructors
RevProxyAppSpec | |
Fields
|
data RevProxyRoute Source #
Constructors
RevProxyRoute | |
Fields
|
Instances
Show RevProxyRoute Source # | |
Defined in Network.Wai.Application.Classic.Types Methods showsPrec :: Int -> RevProxyRoute -> ShowS # show :: RevProxyRoute -> String # showList :: [RevProxyRoute] -> ShowS # | |
Eq RevProxyRoute Source # | |
Defined in Network.Wai.Application.Classic.Types Methods (==) :: RevProxyRoute -> RevProxyRoute -> Bool # (/=) :: RevProxyRoute -> RevProxyRoute -> Bool # |
revProxyApp :: ClassicAppSpec -> RevProxyAppSpec -> RevProxyRoute -> Application Source #
Relaying any requests as reverse proxy.
Path
fromString :: IsString a => String -> a #
(</>) :: Path -> Path -> Path Source #
Appending with the file separator.
>>>
"/foo" </> "bar"
"/foo/bar">>>
"/foo/" </> "bar"
"/foo/bar">>>
"/foo" </> "/bar"
"/foo/bar">>>
"/foo/" </> "/bar"
"/foo/bar"
hasTrailingPathSeparator :: Path -> Bool Source #
Checking if the path ends with the path separator.
>>>
hasTrailingPathSeparator "/foo/bar/"
True>>>
hasTrailingPathSeparator "/foo/bar"
False
type Path = ByteString Source #
File path.
pathString :: Path -> String Source #
(<\>) :: Path -> Path -> Path Source #
Removing prefix. The prefix of the second argument is removed from the first argument.
>>>
"foobar" <\> "foo"
"bar">>>
"foo" <\> "foobar"
"">>>
"foobar" <\> "baz"
"bar"
breakAtSeparator :: Path -> (Path, Path) Source #
Breaking at the first path separator.
>>>
breakAtSeparator "/foo/bar/baz"
("","/foo/bar/baz")>>>
breakAtSeparator "foo/bar/baz"
("foo","/bar/baz")>>>
breakAtSeparator "foo"
("foo","")
hasLeadingPathSeparator :: Path -> Bool Source #
Checking if the path ends with the path separator.
>>>
hasLeadingPathSeparator "/foo/bar"
True>>>
hasLeadingPathSeparator "foo/bar"
False
Misc
hostPort :: Request -> (ByteString, ByteString) Source #