Copyright | Copyright (C) 2004-2011 John Goerzen |
---|---|
License | BSD-3-Clause |
Stability | experimental |
Portability | systems with networking |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
This module provides an infrastructure to simplify server design.
Written by John Goerzen, jgoerzen@complete.org
Please note: this module is designed to work with TCP, UDP, and Unix domain sockets, but only TCP sockets have been tested to date.
This module is presently under-documented. For an example of usage, please see the description of Network.FTP.Server.
Synopsis
- data InetServerOptions = InetServerOptions {
- listenQueueSize :: Int
- portNumber :: PortNumber
- interface :: HostAddress
- reuse :: Bool
- family :: Family
- sockType :: SocketType
- protoStr :: String
- simpleTCPOptions :: Int -> InetServerOptions
- data SocketServer = SocketServer {}
- type HandlerT = Socket -> SockAddr -> SockAddr -> IO ()
- serveTCPforever :: InetServerOptions -> HandlerT -> IO ()
- setupSocketServer :: InetServerOptions -> IO SocketServer
- handleOne :: SocketServer -> HandlerT -> IO ()
- serveForever :: SocketServer -> HandlerT -> IO ()
- closeSocketServer :: SocketServer -> IO ()
- loggingHandler :: String -> Priority -> HandlerT -> HandlerT
- threadedHandler :: HandlerT -> HandlerT
- handleHandler :: (Handle -> SockAddr -> SockAddr -> IO ()) -> HandlerT
Generic Options and Types
data InetServerOptions Source #
Options for your server.
InetServerOptions | |
|
Instances
Eq InetServerOptions Source # | |
Defined in Network.SocketServer (==) :: InetServerOptions -> InetServerOptions -> Bool # (/=) :: InetServerOptions -> InetServerOptions -> Bool # | |
Show InetServerOptions Source # | |
Defined in Network.SocketServer showsPrec :: Int -> InetServerOptions -> ShowS # show :: InetServerOptions -> String # showList :: [InetServerOptions] -> ShowS # |
:: Int | Port Number |
-> InetServerOptions |
Get Default options. You can always modify it later.
data SocketServer Source #
Instances
Eq SocketServer Source # | |
Defined in Network.SocketServer (==) :: SocketServer -> SocketServer -> Bool # (/=) :: SocketServer -> SocketServer -> Bool # | |
Show SocketServer Source # | |
Defined in Network.SocketServer showsPrec :: Int -> SocketServer -> ShowS # show :: SocketServer -> String # showList :: [SocketServer] -> ShowS # |
type HandlerT = Socket -> SockAddr -> SockAddr -> IO () Source #
The main handler type.
The first parameter is the socket itself.
The second is the address of the remote endpoint.
The third is the address of the local endpoint.
TCP server convenient setup
:: InetServerOptions | Server options |
-> HandlerT | Handler function |
-> IO () |
Convenience function to completely set up a TCP
SocketServer
and handle all incoming requests.
This function is literally this:
serveTCPforever options func = do sockserv <- setupSocketServer options serveForever sockserv func
Lower-Level Processing
setupSocketServer :: InetServerOptions -> IO SocketServer Source #
Takes some options and sets up the SocketServer
. I will bind
and begin listening, but will not accept any connections itself.
handleOne :: SocketServer -> HandlerT -> IO () Source #
Handle one incoming request from the given SocketServer
.
serveForever :: SocketServer -> HandlerT -> IO () Source #
Handle all incoming requests from the given SocketServer
.
closeSocketServer :: SocketServer -> IO () Source #
Close the socket server. Does not terminate active handlers, if any.
Combinators
:: String | Name of logger to use |
-> Priority | Priority of logged messages |
-> HandlerT | Handler to call after logging |
-> HandlerT | Resulting handler |
Log each incoming connection using the interface in System.Log.Logger.
Log when the incoming connection disconnects.
Also, log any failures that may occur in the child handler.
Handle each incoming connection in its own thread to make the server multi-tasking.
Give your handler function a Handle instead of a Socket.
The Handle will be opened with ReadWriteMode (you use one handle for both directions of the Socket). Also, it will be initialized with LineBuffering.
Unlike other handlers, the handle will be closed when the function returns. Therefore, if you are doing threading, you should to it before you call this handler.