]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Httpd.hs
Code cleanup (preparation for ditz/lucu-1)
[Lucu.git] / Network / HTTP / Lucu / Httpd.hs
index a49a81d4107d21d7f110b774e89a16ebc23cc9ee..1d0f2b8a5c626d3aa8175c7d07927b88fdeff1cc 100644 (file)
@@ -1,31 +1,72 @@
+-- |The entry point of Lucu httpd.
 module Network.HTTP.Lucu.Httpd
-    ( runHttpd        -- Config -> ResTree -> IO ()
+    ( FallbackHandler
+    , runHttpd
     )
     where
 
 import           Control.Concurrent
-import           Control.Concurrent.STM
-import qualified Data.ByteString.Lazy.Char8 as B
-import           Data.ByteString.Lazy.Char8 (ByteString)
-import           Network
+import           Network hiding (accept)
 import           Network.HTTP.Lucu.Config
 import           Network.HTTP.Lucu.Interaction
 import           Network.HTTP.Lucu.RequestReader
-import           Network.HTTP.Lucu.Resource
+import           Network.HTTP.Lucu.Resource.Tree
 import           Network.HTTP.Lucu.ResponseWriter
-import           System.IO
+import           Network.HTTP.Lucu.SocketLike
+import           System.Posix.Signals
 
-
-runHttpd :: Config -> ResTree -> IO ()
-runHttpd cnf table
+-- |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 @'System.Posix.Signals.installHandler'
+-- 'System.Posix.Signals.sigPIPE' 'System.Posix.Signals.Ignore'
+-- 'Prelude.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
+-- >              }
+runHttpd :: Config -> ResTree -> [FallbackHandler] -> IO ()
+runHttpd cnf tree fbs
     = withSocketsDo $
-      do so <- listenOn (cnfServerPort cnf)
-         loop so
+      do _ <- installHandler sigPIPE Ignore Nothing
+
+         case cnfSSLConfig cnf of
+           Nothing
+               -> return ()
+           Just scnf
+               -> do so       <- listenOn (sslServerPort scnf)
+                     _loopTID <- forkIO $ httpLoop (sslContext scnf, so)
+                     return ()
+         
+         httpLoop =<< listenOn (cnfServerPort cnf)
     where
-      loop :: Socket -> IO ()
-      loop so
-          = do (h, host, _) <- accept so
-               tQueue       <- newInteractionQueue
-               readerTID    <- forkIO $ requestReader cnf table h host tQueue
-               writerTID    <- forkIO $ responseWriter h tQueue readerTID
-               loop so
+      httpLoop :: SocketLike s => s -> IO ()
+      httpLoop so
+          = do (h, addr)  <- accept so
+               tQueue     <- newInteractionQueue
+               readerTID  <- forkIO $ requestReader cnf tree fbs h addr tQueue
+               _writerTID <- forkIO $ responseWriter cnf h tQueue readerTID
+               httpLoop so