{-# LANGUAGE QuasiQuotes #-} module Hack.Contrib.Response where import Hack import Hack.Contrib.Constants import MPSUTF8 import Prelude hiding ((.), (^), (>), (+)) import Data.Map (toList) import Data.Maybe header :: String -> Response -> Maybe String header s r = r.headers.reverse.lookup s has_header :: String -> Response -> Bool has_header s r = r.header s .isJust set_header :: String -> String -> Response -> Response set_header k v r = r { headers = (r.headers ++ [(k,v)] ) .to_h .toList } set_content_type :: String -> Response -> Response set_content_type s r = r.set_header _ContentType s set_content_length :: Int -> Response -> Response set_content_length i r = r.set_header _ContentLength (i.show) set_body :: String -> Response -> Response set_body s r = r { body = s } set_status :: Int -> Response -> Response set_status i r = r { status = i } set_last_modified :: String -> Response -> Response set_last_modified s r = r.set_header _LastModified s