Network.HTTP.Lucu.Httpd
Description
The entry point of Lucu httpd.
- type FallbackHandler = [String] -> IO (Maybe ResourceDef)
- runHttpd :: Config -> ResTree -> [FallbackHandler] -> IO ()
Documentation
type FallbackHandler = [String] -> IO (Maybe ResourceDef)Source
FallbackHandler is an extra resource handler for resources which
can't be statically located somewhere in the resource tree. The
Lucu httpd first search for a resource in the tree, and then call
fallback handlers to ask them for a resource. If all of the
handlers returned Nothing, the httpd responds with 404
Not Found.
runHttpd :: Config -> ResTree -> [FallbackHandler] -> IO ()Source
This is the entry point of Lucu httpd. It listens to a socket and
waits for clients. Computation of runHttpd never stops by itself
so the only way to stop it is to raise an exception in the thread
computing it.
Note that runHttpd automatically makes SIGPIPE be ignored by
computing . This can hardly cause a problem but it may do.
installHandler
sigPIPE Ignore
Nothing
Example:
module Main where
import Network.HTTP.Lucu
main :: IO ()
main = let config = defaultConfig
resources = mkResTree [ ([], helloWorld) ]
in
runHttpd config resourcees []
helloWorld :: ResourceDef
helloWorld = ResourceDef {
resUsesNativeThread = False
, resIsGreedy = False
, resGet
= Just $ do setContentType $ read "text/plain"
output "Hello, world!"
, resHead = Nothing
, resPost = Nothing
, resPut = Nothing
, resDelete = Nothing
}