{-# LANGUAGE QuasiQuotes #-}

module Hack.Contrib.Request where

import Hack hiding (body)
import Hack.Contrib.Constants

import Prelude hiding ((.), (^), (>), (+))
import MPSUTF8
import Hack.Contrib.Utils
import Data.Maybe
import Network.CGI.Protocol
import Network.CGI.Cookie
import Data.ByteString.Lazy.Char8 (ByteString)
import qualified Data.ByteString.Lazy.Char8 as B

-- import qualified Happstack.Server.MessageWrap as HM
-- import qualified Happstack.Server.HTTP.Types as HT

body :: Env -> ByteString
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

content_type :: Env -> String
content_type env = env.http.get _ContentType .fromMaybe ""

media_type :: Env -> String
media_type env = env.content_type.split "\\s*[;,]\\s*" .first.lower

media_type_params :: Env -> [(String, String)]
media_type_params env
  | env.content_type.empty = []
  | otherwise = 
      env
        .content_type
        .split "\\s*[;,]\\s"
        .drop 1
        .map (split "=")
        .select (length > is 2)
        .map tuple2
        .map_fst lower

content_charset :: Env -> String
content_charset env = env.media_type_params.lookup "charset" .fromMaybe ""

host :: Env -> String
host env = env.http.get _Host .fromMaybe (env.server_name) .gsub ":\\d+\\z" ""

params :: Env -> [(String, String)]
params env =
  if env.query_string.empty 
    then []
    else env.query_string.formDecode

inputs :: Env -> [(String, String)]
inputs env = 
  env
    .http
    .map_fst (upper > gsub "-" "_") -- cgi env use all cap letters
    .(("REQUEST_METHOD", env.request_method.show) : ) -- for cgi request
    .flip decodeInput (env.body)
    .fst
    .concatMap to_headers
  where
    to_headers (k, input) = case input.inputFilename of
      Nothing -> [(k, input.inputValue.B.unpack)]
      Just name -> 
        [  (k, input.inputValue.B.unpack)
        ,  ("hack_input_file_name_" ++ k, name)
        ]

referer :: Env -> String
referer = http > get _Referer > fromMaybe "/"

cookies :: Env -> [(String, String)]
cookies env = case env.http.get _Cookie of
  Nothing -> []
  Just s -> s.readCookies

fullpath :: Env -> String
fullpath env = 
  if env.query_string.empty 
    then env.path 
    else env.path ++ "?" ++ env.query_string

set_http :: String -> String -> Env -> Env
set_http k v env = env {http = env.http.put k v}

set_custom :: String -> String -> Env -> Env
set_custom k v env = env {hackHeaders = env.custom.put k v}

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 ""