module Hack.Handler.Kibro (run) where import qualified Hack as Hack import Kibro import Network.CGI hiding (Html) import Network.URI import Data.Default import Prelude hiding ((.), (^)) import System.IO (.) :: a -> (a -> b) -> b a . f = f a infixl 9 . run :: Hack.Application -> IO () run app' = startKibro [("", handle app')] where get_env = do uri <- requestURI request_method' <- requestMethod >>= readMethod let script_name' = "" let path_info' = uri.uriPath let query_string' = uri.uriQuery server_name' <- serverName server_port' <- serverPort hack_input' <- getBodyFPS http' <- getVars def { Hack.requestMethod = request_method' , Hack.scriptName = script_name' , Hack.pathInfo = path_info' , Hack.queryString = query_string'.remove_question_mark , Hack.serverName = server_name' , Hack.serverPort = server_port' , Hack.hackInput = hack_input' , Hack.http = http' } .return where remove_question_mark = dropWhile (== '?') readMethod :: Monad m => String -> m Hack.RequestMethod readMethod s = case reads s of ((x, _):_) -> return x [] -> fail $ "Unknown request method: " ++ s handle app = do env <- get_env response <- app env .liftIO -- set response response.Hack.headers.mapM_ (uncurry setHeader) response.Hack.status.show.setHeader "Status" response.Hack.body.outputFPS