{-# LANGUAGE CPP #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS -fno-warn-orphans #-}
module Happstack.Server.SimpleHTTP
(
simpleHTTP
, simpleHTTP'
, simpleHTTP''
, simpleHTTPWithSocket
, simpleHTTPWithSocket'
, bindPort
, bindIPv4
, parseConfig
, waitForTermination
, module Happstack.Server.Monads
, module Happstack.Server.Auth
, module Happstack.Server.Cookie
, module Happstack.Server.Error
, module Happstack.Server.Response
, module Happstack.Server.Routing
, module Happstack.Server.Proxy
, module Happstack.Server.RqData
, module Happstack.Server.Validation
, module Happstack.Server.Types
) where
import Happstack.Server.Auth
import Happstack.Server.Monads
import Happstack.Server.Cookie
import Happstack.Server.Error
import Happstack.Server.Types
import Happstack.Server.Proxy
import Happstack.Server.Routing
import Happstack.Server.RqData
import Happstack.Server.Response
import Happstack.Server.Validation
import Control.Monad
import Data.Maybe (fromMaybe)
import qualified Data.Version as DV
import Happstack.Server.Internal.Monads (FilterFun, WebT(..), unFilterFun, runServerPartT, ununWebT)
import qualified Happstack.Server.Internal.Listen as Listen (listen, listen',listenOn, listenOnIPv4)
import Network (Socket)
import qualified Paths_happstack_server as Cabal
import System.Console.GetOpt ( OptDescr(Option)
, ArgDescr(ReqArg)
, ArgOrder(Permute)
, getOpt
)
#ifdef UNIX
import Control.Concurrent.MVar
import System.Posix.Signals hiding (Handler)
import System.Posix.IO ( stdInput )
import System.Posix.Terminal ( queryTerminal )
#endif
ho :: [OptDescr (Conf -> Conf)]
ho = [Option [] ["http-port"] (ReqArg (\h c -> c { port = readDec' h }) "port") "port to bind http server"]
parseConfig :: [String] -> Either [String] Conf
parseConfig args
= case getOpt Permute ho args of
(flags,_,[]) -> Right $ foldr ($) nullConf flags
(_,_,errs) -> Left errs
simpleHTTP :: (ToMessage a) => Conf -> ServerPartT IO a -> IO ()
simpleHTTP = simpleHTTP' id
simpleHTTP' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b)
-> Conf -> ServerPartT m a -> IO ()
simpleHTTP' toIO conf hs =
Listen.listen conf (\req -> runValidator (fromMaybe return (validator conf)) =<< (simpleHTTP'' (mapServerPartT toIO hs) req))
simpleHTTP'' :: (ToMessage b, Monad m, Functor m) => ServerPartT m b -> Request -> m Response
simpleHTTP'' hs req = (runWebT $ runServerPartT hs req) >>= (return . (maybe standardNotFound id))
where
standardNotFound = setHeader "Content-Type" "text/html" $ (toResponse notFoundHtml){rsCode=404}
simpleHTTPWithSocket :: (ToMessage a) => Socket -> Conf -> ServerPartT IO a -> IO ()
simpleHTTPWithSocket = simpleHTTPWithSocket' id
simpleHTTPWithSocket' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b)
-> Socket -> Conf -> ServerPartT m a -> IO ()
simpleHTTPWithSocket' toIO socket conf hs =
Listen.listen' socket conf (\req -> runValidator (fromMaybe return (validator conf)) =<< (simpleHTTP'' (mapServerPartT toIO hs) req))
bindPort :: Conf -> IO Socket
bindPort conf = Listen.listenOn (port conf)
bindIPv4 :: String
-> Int
-> IO Socket
bindIPv4 addr prt = Listen.listenOnIPv4 addr prt
runWebT :: forall m b. (Functor m, ToMessage b) => WebT m b -> m (Maybe Response)
runWebT = (fmap . fmap) appFilterToResp . ununWebT
where
appFilterToResp :: (Either Response b, FilterFun Response) -> Response
appFilterToResp (e, ff) = unFilterFun ff $ either id toResponse e
notFoundHtml :: String
notFoundHtml =
"<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 4.01//EN\" \"http://www.w3.org/TR/html4/strict.dtd\">"
++ "<html><head><title>Happstack "
++ ver ++ " File not found</title></head>"
++ "<body><h1>Happstack " ++ ver ++ "</h1>"
++ "<p>Your file is not found<br>"
++ "To try again is useless<br>"
++ "It is just not here</p>"
++ "</body></html>"
where ver = DV.showVersion Cabal.version
waitForTermination :: IO ()
waitForTermination
= do
#ifdef UNIX
istty <- queryTerminal stdInput
mv <- newEmptyMVar
void $ installHandler softwareTermination (CatchOnce (putMVar mv ())) Nothing
void $ installHandler lostConnection (CatchOnce (putMVar mv ())) Nothing
case istty of
True -> void $ installHandler keyboardSignal (CatchOnce (putMVar mv ())) Nothing
False -> return ()
takeMVar mv
#else
let loop 'e' = return ()
loop _ = getChar >>= loop
loop 'c'
#endif