-- |The entry point of Lucu httpd.
module Network.HTTP.Lucu.Httpd
    ( FallbackHandler
    , runHttpd
    )
    where

import           Control.Concurrent
import           Network
import qualified Network.Socket as So
import           Network.HTTP.Lucu.Config
import           Network.HTTP.Lucu.Interaction
import           Network.HTTP.Lucu.RequestReader
import           Network.HTTP.Lucu.Resource.Tree
import           Network.HTTP.Lucu.ResponseWriter
import           System.IO
import           System.Posix.Signals

-- |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 installHandler sigPIPE Ignore Nothing
         so <- listenOn (cnfServerPort cnf)
         loop so
    where
      loop :: Socket -> IO ()
      loop so
          -- 本當は Network.accept を使ひたいが、このアクションは勝手に
          -- リモートのIPを逆引きするので、使へない。
          = do (h, addr)  <- accept' so
               tQueue     <- newInteractionQueue
               readerTID  <- forkIO $ requestReader cnf tree fbs h addr tQueue
               _writerTID <- forkIO $ responseWriter cnf h tQueue readerTID
               loop so

      accept' :: Socket -> IO (Handle, So.SockAddr)
      accept' soSelf
          = do (soPeer, addr) <- So.accept soSelf
               hPeer          <- So.socketToHandle soPeer ReadWriteMode
               return (hPeer, addr)