| Portability | requires mtl | 
|---|---|
| Stability | provisional | 
| Maintainer | Happstack team <happs@googlegroups.com> | 
| Safe Haskell | None | 
Happstack.Server.SimpleHTTP
Contents
Description
simpleHTTP is a self-contained HTTP server which can be used to
 run a ServerPart.
A very simple, "Hello World!" web app looks like:
import Happstack.Server main = simpleHTTP nullConf $ ok "Hello World!"
By default the server will listen on port 8000. Run the app and point your browser at: http://localhost:8000/
For FastCGI support see: http://hackage.haskell.org/package/happstack-fastcgi
- simpleHTTP :: ToMessage a => Conf -> ServerPartT IO a -> IO ()
- simpleHTTP' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Conf -> ServerPartT m a -> IO ()
- simpleHTTP'' :: (ToMessage b, Monad m, Functor m) => ServerPartT m b -> Request -> m Response
- simpleHTTPWithSocket :: ToMessage a => Socket -> Conf -> ServerPartT IO a -> IO ()
- simpleHTTPWithSocket' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Socket -> Conf -> ServerPartT m a -> IO ()
- bindPort :: Conf -> IO Socket
- bindIPv4 :: String -> Int -> IO Socket
- parseConfig :: [String] -> Either [String] Conf
- waitForTermination :: IO ()
- module Happstack.Server.Monads
- module Happstack.Server.Auth
- module Happstack.Server.Cookie
- module Happstack.Server.Error
- module Happstack.Server.Response
- module Happstack.Server.Routing
- module Happstack.Server.Proxy
- module Happstack.Server.RqData
- module Happstack.Server.Validation
- module Happstack.Server.Types
SimpleHTTP
simpleHTTP :: ToMessage a => Conf -> ServerPartT IO a -> IO ()Source
start the server, and handle requests using the supplied
 ServerPart.
This function will not return, though it may throw an exception.
NOTE: The server will only listen on IPv4 due to portability issues
 in the Network module. For IPv6 support, use
 simpleHTTPWithSocket with custom socket.
simpleHTTP' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Conf -> ServerPartT m a -> IO ()Source
A combination of simpleHTTP'' and mapServerPartT.  See
 mapServerPartT for a discussion of the first argument of this
 function. 
NOTE: This function always binds to IPv4 ports until Network
 module is fixed to support IPv6 in a portable way. Use
 simpleHTTPWithSocket with custom socket if you want different
 behaviour.
simpleHTTP'' :: (ToMessage b, Monad m, Functor m) => ServerPartT m b -> Request -> m ResponseSource
Generate a result from a ServerPartT and a Request. This is
 mainly used by CGI (and fast-cgi) wrappers.
simpleHTTPWithSocket :: ToMessage a => Socket -> Conf -> ServerPartT IO a -> IO ()Source
Run simpleHTTP with a previously bound socket. Useful if you
 want to run happstack as user on port 80. Use something like this:
 import System.Posix.User (setUserID, UserEntry(..), getUserEntryForName)
 main = do
     let conf = nullConf { port = 80 }
     socket <- bindPort conf
     -- do other stuff as root here
     getUserEntryForName "www" >>= setUserID . userID
     -- finally start handling incoming requests
     tid <- forkIO $ simpleHTTPWithSocket socket Nothing conf impl
Note: It's important to use the same conf (or at least the same
 port) for bindPort and simpleHTTPWithSocket.
simpleHTTPWithSocket' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Socket -> Conf -> ServerPartT m a -> IO ()Source
Like simpleHTTP' with a socket.
bindPort :: Conf -> IO SocketSource
Bind port and return the socket for use with simpleHTTPWithSocket. This
 function always binds to IPv4 ports until Network module is fixed
 to support IPv6 in a portable way.
Arguments
| :: String | IP address to bind to (must be an IP address and not a host name) | 
| -> Int | port number to bind to | 
| -> IO Socket | 
Bind to ip and port and return the socket for use with simpleHTTPWithSocket.
 import Happstack.Server
 main = do let conf = nullConf
               addr = "127.0.0.1"
           s <- bindIPv4 addr (port conf)
           simpleHTTPWithSocket s conf $ ok $ toResponse $ 
             "now listening on ip addr " ++ addr ++ 
             " and port " ++ show (port conf)
waitForTermination :: IO ()Source
Wait for a signal. On unix, a signal is sigINT or sigTERM (aka Control-C).
On windows, the signal is entering: e return
Re-exported modules
Basic ServerMonad functionality
module Happstack.Server.Monads
HTTP Realm Authentication
module Happstack.Server.Auth
Create and Set Cookies (see also Happstack.Server.RqData)
module Happstack.Server.Cookie
Error Handling
module Happstack.Server.Error
Creating Responses
module Happstack.Server.Response
Request Routing
module Happstack.Server.Routing
Proxying
module Happstack.Server.Proxy
Looking up values in Query String, Request Body, and Cookies
module Happstack.Server.RqData
Output Validation
module Happstack.Server.Validation
module Happstack.Server.Types