{-# LANGUAGE QuasiQuotes #-} module Hack.Request where import Hack import Prelude hiding ((.), (^), (>), lookup, (+)) import MPSUTF8 import Hack.Utils import List (lookup) import Data.Maybe body :: Env -> String body = hack_input scheme :: Env -> String scheme = hack_url_scheme > show > lower port :: Env -> Int port = server_port path :: Env -> String path env = env.script_name ++ env.path_info fullpath :: Env -> String fullpath env = if env.query_string.empty then env.path else env.path ++ "?" ++ env.query_string http_ :: String -> Env -> Maybe String http_ s env = env.http.reverse.lookup ("HTTP_" ++s) custom_ :: String -> Env -> Maybe String custom_ s env = env.custom.reverse.lookup s host :: Env -> String host env = env.http_"HOST" .fromMaybe (env.server_name) .gsub ":\\d+\\z" "" url :: Env -> String url env = [ env.scheme , "://" , env.host , port_string , env.fullpath ] .join' where port_string = if (env.scheme.is "https" && env.port.is_not 443 || env.scheme.is "http" && env.port.is_not 80 ) then ":" ++ env.server_port.show else ""