Lucu-0.7.0.1: HTTP Daemonic Library

Network.HTTP.Lucu

Contents

Description

Lucu is an HTTP daemonic library. It can be embedded in any Haskell program and runs in an independent thread.

Features:

Full support of HTTP\1.1/
Lucu supports request pipelining, chunked I/O, ETag comparison and "100 Continue".
Performance
Lucu doesn't fork/exec to handle requests like CGI. It just spawns a new thread. Inter-process communication is done with STM.
Affinity for RESTafarians
Lucu is a carefully designed web server for RESTful applications.
SSL connections
Lucu can handle HTTP connections over SSL layer.

Lucu is not a replacement for Apache or lighttpd. It is intended to be used to create an efficient web-based RESTful application without messing around FastCGI. It is also intended to be run behind a reverse-proxy so it doesn't have the following (otherwise essential) facilities:

Logging
Lucu doesn't log any requests from any clients.
Client Filtering
Lucu always accepts any clients. No IP filter is implemented.
Bandwidth Limitting
Lucu doesn't limit bandwidth it consumes.
Protection Against Wicked Clients
Lucu is fragile against wicked clients. No attacker should be able to cause a buffer-overflow but can possibly DoS it.

Synopsis

Entry Point

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 installHandler sigPIPE Ignore Nothing. This can hardly cause a problem but it may do.

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
              }

Configuration

Resource Tree

data ResourceDef Source

ResourceDef is basically a set of Resource monads for each HTTP methods.

Constructors

ResourceDef 

Fields

resUsesNativeThread :: !Bool

Whether to run a Resource on a native thread (spawned by forkOS) or to run it on a user thread (spanwed by forkIO). Generally you don't need to set this field to True.

resIsGreedy :: !Bool

Whether to be greedy or not.

Say a client is trying to access /aaa/bbb/ccc. If there is a greedy resource at /aaa/bbb, it is always chosen even if there is another resource at /aaa/bbb/ccc. If the resource at /aaa/bbb is not greedy, it is just ignored. Greedy resources are like CGI scripts.

resGet :: !(Maybe (Resource ()))

A Resource to be run when a GET request comes for the 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.

resHead :: !(Maybe (Resource ()))

A Resource to be run when a HEAD request comes for the resource path. If resHead is Nothing, the system runs resGet instead. If resGet is also Nothing, the system responds "405 Method Not Allowed" for HEAD requests.

resPost :: !(Maybe (Resource ()))

A Resource to be run when a POST request comes for the resource path. If resPost is Nothing, the system responds "405 Method Not Allowed" for POST requests.

resPut :: !(Maybe (Resource ()))

A Resource to be run when a PUT request comes for the resource path. If resPut is Nothing, the system responds "405 Method Not Allowed" for PUT requests.

resDelete :: !(Maybe (Resource ()))

A Resource to be run when a DELETE request comes for the resource path. If resDelete is Nothing, the system responds "405 Method Not Allowed" for DELETE requests.

emptyResource :: ResourceDefSource

emptyResource is a resource definition with no actual handlers. You can construct a ResourceDef by selectively overriding emptyResource. It is defined as follows:

   emptyResource = ResourceDef {
                     resUsesNativeThread = False
                   , resIsGreedy         = False
                   , resGet              = Nothing
                   , resHead             = Nothing
                   , resPost             = Nothing
                   , resPut              = Nothing
                   , resDelete           = Nothing
                   }

data ResTree Source

ResTree is an opaque structure which is a map from resource path to ResourceDef.

mkResTree :: [([String], ResourceDef)] -> ResTreeSource

mkResTree converts a list of (path, def) to a ResTree e.g.

   mkResTree [ ([]        , Network.HTTP.Lucu.StaticFile.staticFile "/usr/include/stdio.h" ) -- /
             , (["unistd"], Network.HTTP.Lucu.StaticFile.staticFile "/usr/include/unistd.h") -- /unistd
             ]

Resource Monad

Things to be used in the Resource monad

Status Code

Abortion

abort :: MonadIO m => StatusCode -> [(String, String)] -> Maybe String -> m aSource

Computation of abort status headers msg aborts the Network.HTTP.Lucu.Resource.Resource monad with given status, additional response headers, and optional message string.

What this really does is to throw a special Exception. The exception will be caught by the Lucu system.

  1. If the Network.HTTP.Lucu.Resource.Resource is in the /Deciding Header/ or any precedent states, it is possible to use the status and such like as a HTTP response to be sent to the client.
  2. Otherwise the HTTP response can't be modified anymore so the only possible thing the system can do is to dump it to the stderr. See cnfDumpTooLateAbortionToStderr.

Note that the status code doesn't have to be an error code so you can use this action for redirection as well as error reporting e.g.

 abort MovedPermanently
       [("Location", "http://example.net/")]
       (Just "It has been moved to example.net")

abortPurely :: StatusCode -> [(String, String)] -> Maybe String -> aSource

This is similar to abort but computes it with unsafePerformIO.

abortA :: ArrowIO a => a (StatusCode, ([(String, String)], Maybe String)) cSource

Computation of abortA -< (status, (headers, msg)) just computes abort in an ArrowIO.

ETag

data ETag Source

An entity tag is made of a weakness flag and a opaque string.

Constructors

ETag 

Fields

etagIsWeak :: !Bool

The weakness flag. Weak tags looks like W/"blahblah" and strong tags are like "blahblah".

etagToken :: !String

An opaque string. Only characters from 0x20 (sp) to 0x7e (~) are allowed.

Instances

strongETag :: String -> ETagSource

This is equivalent to ETag False. If you want to generate an ETag from a file, try using Network.HTTP.Lucu.StaticFile.generateETagFromFile.

weakETag :: String -> ETagSource

This is equivalent to ETag True.

MIME Type

data MIMEType Source

MIMEType "major" "minor" [("name", "value")] represents "major/minor; name=value".

Constructors

MIMEType 

Fields

mtMajor :: !String
 
mtMinor :: !String
 
mtParams :: ![(String, String)]
 

Authorization

data AuthChallenge Source

Authorization challenge to be sent to client with "WWW-Authenticate" header. See Network.HTTP.Lucu.Resource.setWWWAuthenticate.

data AuthCredential Source

Authorization credential to be sent by client with "Authorization" header. See Network.HTTP.Lucu.Resource.getAuthorization.

Utility

Static file handling