]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Httpd.hs
hlint
[Lucu.git] / Network / HTTP / Lucu / Httpd.hs
index 883a9a651f4999a893811670ebb114badc5e4bad..a5f974978a4c6e5ccc4baad408d61bd5ce69f661 100644 (file)
@@ -4,8 +4,7 @@
   #-}
 -- |The entry point of Lucu httpd.
 module Network.HTTP.Lucu.Httpd
-    ( FallbackHandler
-    , runHttpd
+    ( runHttpd
     )
     where
 import Control.Concurrent
@@ -16,11 +15,12 @@ import Data.Maybe
 import Network.BSD
 import Network.Socket
 import Network.HTTP.Lucu.Config
+import Network.HTTP.Lucu.Dispatcher
 import Network.HTTP.Lucu.Interaction
 import Network.HTTP.Lucu.RequestReader
-import Network.HTTP.Lucu.Resource.Tree
 import Network.HTTP.Lucu.ResponseWriter
 import Network.HTTP.Lucu.SocketLike as SL
+import Prelude.Unicode
 
 -- |This is the entry point of Lucu httpd. It listens to a socket and
 -- waits for clients. 'runHttpd' never stops by itself so the only way
@@ -28,26 +28,31 @@ import Network.HTTP.Lucu.SocketLike as SL
 --
 -- Example:
 --
--- > {-# LANGUAGE OverloadedStrings #-}
--- > module Main where
--- > import Network.HTTP.Lucu
--- > 
--- > main :: IO ()
--- > main = let config    = defaultConfig
--- >            resources = mkResTree [ ([], helloWorld) ]
--- >        in
--- >          runHttpd config resourcees []
--- >
--- > helloWorld :: ResourceDef
--- > helloWorld = emptyResource {
--- >                resGet
--- >                  = Just $ do setContentType $ parseMIMEType "text/plain"
--- >                              putChunk "Hello, world!"
--- >              }
-runHttpd ∷ Config → ResTree → [FallbackHandler] → IO ()
-runHttpd cnf tree fbs
-    = withSocketsDo $
-      do let launchers
+-- @
+--   {-\# LANGUAGE OverloadedStrings \#-}
+--   {-\# LANGUAGE QuasiQuotes \#-}
+--   module Main where
+--   import qualified "Data.Collections" as C
+--   import "Network"
+--   import "Network.HTTP.Lucu"
+--
+--   main :: 'IO' ()
+--   main = let config = 'defaultConfig'
+--              tree   :: 'ResourceTree'
+--              tree   = C.fromList [ ([], 'nonGreedy' helloWorld) ]
+--          in
+--            'Network.withSocketsDo' '.' 'runHttpd' config '$' 'resourceMap' tree
+--
+--   helloWorld :: 'Network.HTTP.Lucu.Resource'
+--   helloWorld = C.fromList
+--                [ ( 'Network.HTTP.Lucu.GET'
+--                  , do 'Network.HTTP.Lucu.setContentType' ['Network.HTTP.Lucu.mimeType'| text/plain |]
+--                       'Network.HTTP.Lucu.putChunk' \"Hello, world!\"
+--                }
+-- @
+runHttpd ∷ HostMapper α ⇒ Config → α → IO ()
+runHttpd cnf hm
+    = do let launchers
                  = catMaybes
                    [ do addr ← cnfServerV4Addr cnf
                         return ( launchListener =≪ listenOn AF_INET addr (cnfServerPort cnf)
@@ -75,8 +80,8 @@ runHttpd cnf tree fbs
       launchListener so
           = do p ← SL.socketPort so
                -- FIXME: Don't throw away the thread ID as we can't
-               -- kill it later then. [1]
-               void $ forkIO $ httpLoop p so
+               -- kill it later then.
+               void  forkIO $ httpLoop p so
 
       listenOn ∷ Family → HostName → ServiceName → IO Socket
       listenOn fam host srv
@@ -90,7 +95,9 @@ runHttpd cnf tree fbs
                addrs ← getAddrInfo (Just hints) (Just host) (Just srv)
                let addr = head addrs
                bracketOnError
-                   (socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr))
+                   (socket (addrFamily     addr)
+                           (addrSocketType addr)
+                           (addrProtocol   addr))
                    sClose
                    (\ sock →
                         do setSocketOption sock ReuseAddr 1
@@ -103,9 +110,9 @@ runHttpd cnf tree fbs
       httpLoop port so
           = do (h, addr)  ← SL.accept so
                tQueue     ← mkInteractionQueue
-               readerTID  ← forkIO $ requestReader cnf tree fbs h port addr tQueue
+               readerTID  ← forkIO $ requestReader cnf hm h port addr tQueue
                _writerTID ← forkIO $ responseWriter cnf h tQueue readerTID
                httpLoop port so
 
       waitForever ∷ IO ()
-      waitForever = forever (threadDelay 1000000)
+      waitForever = forever $ threadDelay 1000000