module Happstack.Server.Response
(
ToMessage(..)
, flatten
, toResponseBS
, ok
, noContent
, internalServerError
, badGateway
, badRequest
, unauthorized
, forbidden
, notFound
, prettyResponse
, requestEntityTooLarge
, seeOther
, found
, movedPermanently
, tempRedirect
, setResponseCode
, resp
, ifModifiedSince
) where
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as L
import qualified Data.ByteString.Lazy.UTF8 as LU (fromString)
import qualified Data.Map as M
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
import Data.Time (UTCTime, formatTime)
import Happstack.Server.Internal.Monads (FilterMonad(composeFilter))
import Happstack.Server.Types (Response(..), Request(..), nullRsFlags, getHeader, noContentLength, redirect, result, setHeader, setHeaderBS)
import Happstack.Server.SURI (ToSURI)
import System.Locale (defaultTimeLocale)
import qualified Text.Blaze.Html as Blaze
import qualified Text.Blaze.Html.Renderer.Utf8 as Blaze
import Text.Html (Html, renderHtml)
import qualified Text.XHtml as XHtml (Html, renderHtml)
toResponseBS :: B.ByteString
-> L.ByteString
-> Response
toResponseBS contentType message =
let res = Response 200 M.empty nullRsFlags message Nothing
in setHeaderBS (B.pack "Content-Type") contentType res
class ToMessage a where
toContentType :: a -> B.ByteString
toContentType _ = B.pack "text/plain"
toMessage :: a -> L.ByteString
toMessage = error "Happstack.Server.SimpleHTTP.ToMessage.toMessage: Not defined"
toResponse:: a -> Response
toResponse val =
let bs = toMessage val
res = Response 200 M.empty nullRsFlags bs Nothing
in setHeaderBS (B.pack "Content-Type") (toContentType val)
res
instance ToMessage () where
toContentType _ = B.pack "text/plain"
toMessage () = L.empty
instance ToMessage String where
toContentType _ = B.pack "text/plain; charset=UTF-8"
toMessage = LU.fromString
instance ToMessage T.Text where
toContentType _ = B.pack "text/plain; charset=UTF-8"
toMessage t = L.fromChunks [T.encodeUtf8 t]
instance ToMessage LT.Text where
toContentType _ = B.pack "text/plain; charset=UTF-8"
toMessage = LT.encodeUtf8
instance ToMessage Integer where
toMessage = toMessage . show
instance ToMessage a => ToMessage (Maybe a) where
toContentType _ = toContentType (undefined :: a)
toMessage Nothing = toMessage "nothing"
toMessage (Just x) = toMessage x
instance ToMessage Html where
toContentType _ = B.pack "text/html; charset=UTF-8"
toMessage = LU.fromString . renderHtml
instance ToMessage XHtml.Html where
toContentType _ = B.pack "text/html; charset=UTF-8"
toMessage = LU.fromString . XHtml.renderHtml
instance ToMessage Blaze.Html where
toContentType _ = B.pack "text/html; charset=UTF-8"
toMessage = Blaze.renderHtml
instance ToMessage Response where
toResponse = id
instance ToMessage L.ByteString where
toResponse bs = Response 200 M.empty nullRsFlags bs Nothing
instance ToMessage B.ByteString where
toResponse bs = toResponse (L.fromChunks [bs])
flatten :: (ToMessage a, Functor f) => f a -> f Response
flatten = fmap toResponse
ifModifiedSince :: UTCTime
-> Request
-> Response
-> Response
ifModifiedSince modTime request response =
let repr = formatTime defaultTimeLocale "%a, %d %b %Y %X GMT" modTime
notmodified = getHeader "if-modified-since" request == Just (B.pack $ repr)
in if notmodified
then noContentLength $ result 304 ""
else setHeader "Last-modified" repr response
modifyResponse :: (FilterMonad a m) => (a -> a) -> m()
modifyResponse = composeFilter
setResponseCode :: FilterMonad Response m =>
Int
-> m ()
setResponseCode code
= composeFilter $ \r -> r{rsCode = code}
resp :: (FilterMonad Response m) =>
Int
-> b
-> m b
resp status val = setResponseCode status >> return val
ok :: (FilterMonad Response m) => a -> m a
ok = resp 200
noContent :: (FilterMonad Response m) => a -> m a
noContent val = composeFilter (\r -> noContentLength (r { rsCode = 204, rsBody = L.empty })) >> return val
movedPermanently :: (FilterMonad Response m, ToSURI a) => a -> res -> m res
movedPermanently uri res = do modifyResponse $ redirect 301 uri
return res
found :: (FilterMonad Response m, ToSURI uri) => uri -> res -> m res
found uri res = do modifyResponse $ redirect 302 uri
return res
seeOther :: (FilterMonad Response m, ToSURI uri) => uri -> res -> m res
seeOther uri res = do modifyResponse $ redirect 303 uri
return res
tempRedirect :: (FilterMonad Response m, ToSURI a) => a -> res -> m res
tempRedirect val res = do modifyResponse $ redirect 307 val
return res
badRequest :: (FilterMonad Response m) => a -> m a
badRequest = resp 400
unauthorized :: (FilterMonad Response m) => a -> m a
unauthorized = resp 401
forbidden :: (FilterMonad Response m) => a -> m a
forbidden = resp 403
notFound :: (FilterMonad Response m) => a -> m a
notFound = resp 404
requestEntityTooLarge :: (FilterMonad Response m) => a -> m a
requestEntityTooLarge = resp 413
internalServerError :: (FilterMonad Response m) => a -> m a
internalServerError = resp 500
badGateway :: (FilterMonad Response m) => a -> m a
badGateway = resp 502
prettyResponse :: Response -> String
prettyResponse res@Response{} =
showString "================== Response ================" .
showString "\nrsCode = " . shows (rsCode res) .
showString "\nrsHeaders = " . shows (rsHeaders res) .
showString "\nrsFlags = " . shows (rsFlags res) .
showString "\nrsBody = " . shows (rsBody res) .
showString "\nrsValidator = " $ show (rsValidator res)
prettyResponse res@SendFile{} =
showString "================== Response ================" .
showString "\nrsCode = " . shows (rsCode res) .
showString "\nrsHeaders = " . shows (rsHeaders res) .
showString "\nrsFlags = " . shows (rsFlags res) .
showString "\nrsValidator = " . shows (rsValidator res).
showString "\nsfFilePath = " . shows (sfFilePath res) .
showString "\nsfOffset = " . shows (sfOffset res) .
showString "\nsfCount = " $ show (sfCount res)