module Happstack.Server.Internal.Listen(listen, listen',listenOn,listenOnIPv4) where
import Happstack.Server.Internal.Types (Conf(..), Request, Response)
import Happstack.Server.Internal.Handler (request)
import Happstack.Server.Internal.Socket (acceptLite)
import Happstack.Server.Internal.TimeoutManager (cancel, initialize, register)
import Happstack.Server.Internal.TimeoutSocket as TS
import qualified Control.Concurrent.Thread.Group as TG
import Control.Exception.Extensible as E
import Control.Concurrent (forkIO, killThread, myThreadId)
import Control.Monad
import Network.BSD (getProtocolNumber)
import Network (sClose, Socket)
import Network.Socket as Socket (SocketOption(KeepAlive), setSocketOption,
socket, Family(..), SockAddr,
SocketOption(..), SockAddr(..),
iNADDR_ANY, maxListenQueue, SocketType(..),
bindSocket)
import qualified Network.Socket as Socket (listen, inet_addr)
import System.IO.Error (isFullError)
import System.Posix.Signals
import System.Log.Logger (Priority(..), logM)
log':: Priority -> String -> IO ()
log' = logM "Happstack.Server.HTTP.Listen"
listenOn :: Int -> IO Socket
listenOn portm = do
proto <- getProtocolNumber "tcp"
E.bracketOnError
(socket AF_INET Stream proto)
(sClose)
(\sock -> do
setSocketOption sock ReuseAddr 1
bindSocket sock (SockAddrInet (fromIntegral portm) iNADDR_ANY)
Socket.listen sock (max 1024 maxListenQueue)
return sock
)
listenOnIPv4 :: String
-> Int
-> IO Socket
listenOnIPv4 ip portm = do
proto <- getProtocolNumber "tcp"
hostAddr <- Socket.inet_addr ip
E.bracketOnError
(socket AF_INET Stream proto)
(sClose)
(\sock -> do
setSocketOption sock ReuseAddr 1
bindSocket sock (SockAddrInet (fromIntegral portm) hostAddr)
Socket.listen sock (max 1024 maxListenQueue)
return sock
)
listen :: Conf -> (Request -> IO Response) -> IO ()
listen conf hand = do
let port' = port conf
socketm <- listenOn port'
setSocketOption socketm KeepAlive 1
listen' socketm conf hand
listen' :: Socket -> Conf -> (Request -> IO Response) -> IO ()
listen' s conf hand = do
void $ installHandler openEndedPipe Ignore Nothing
let port' = port conf
fork = case threadGroup conf of
Nothing -> forkIO
Just tg -> \m -> fst `liftM` TG.forkIO tg m
tm <- initialize ((timeout conf) * (10^(6 :: Int)))
log' NOTICE ("Listening for http:// on port " ++ show port')
let eh (x::SomeException) = when ((fromException x) /= Just ThreadKilled) $ log' ERROR ("HTTP request failed with: " ++ show x)
work (sock, hn, p) =
do tid <- myThreadId
thandle <- register tm (killThread tid)
let timeoutIO = TS.timeoutSocketIO thandle sock
request timeoutIO (logAccess conf) (hn,fromIntegral p) hand `E.catch` eh
cancel thandle
sClose sock
loop = forever $ do w <- acceptLite s
fork $ work w
pe e = log' ERROR ("ERROR in http accept thread: " ++ show e)
infi :: IO ()
infi = loop `catchSome` pe >> infi
infi `finally` (sClose s)
void $ installHandler openEndedPipe Ignore Nothing
where
catchSome op h = op `E.catches` [
Handler $ \(e :: ArithException) -> h (toException e),
Handler $ \(e :: ArrayException) -> h (toException e),
Handler $ \(e :: IOException) ->
if isFullError e
then return ()
else throw e
]