{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Network.Wai.Routing.Purescheme.Core.Entity
( EntityResponse
, entity
, NegotiatedResponse
, mapEntity
, withCustomNegotiation
, withCustomNegotiation'
, negotiated
, ok
, created
, notFound
, badRequest
, entityResponse
, requestEntity
)
where
import Network.Wai.Routing.Purescheme.Core.Basic
import Network.Wai.Routing.Purescheme.Core.Internal
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as LBC
import qualified Data.ByteString.Lazy as LBS
import Data.List (find)
import Data.Maybe (fromJust, fromMaybe)
import Data.String.Interpolate.IsString (i)
import Network.HTTP.Media (matchAccept, mapAccept)
import Network.HTTP.Types (Status, ResponseHeaders, notAcceptable406, hAccept, hContentType,
statusMessage, badRequest400, unsupportedMediaType415, ok200, created201, notFound404)
import Network.Wai (Response, ResponseReceived, responseLBS, requestHeaders, strictRequestBody)
data EntityResponse e = EntityResponse Status ResponseHeaders e
data NegotiatedResponse = NegotiatedResponse Status ResponseHeaders [(ByteString, LBS.ByteString)]
instance HasResponseHeaders (EntityResponse a) where
mapResponseHeaders mapf (EntityResponse responseStatus responseHeaders entity) =
EntityResponse responseStatus (mapf responseHeaders) entity
instance HasResponseHeaders (NegotiatedResponse) where
mapResponseHeaders mapf (NegotiatedResponse negotiatedStatus negotiatedHeaders entity) =
NegotiatedResponse negotiatedStatus (mapf negotiatedHeaders) entity
entity :: EntityResponse e -> e
entity (EntityResponse _ _ e) = e
mapEntity :: (a -> b) -> EntityResponse a -> EntityResponse b
mapEntity mapf (EntityResponse responseStatus responseHeaders entity) =
EntityResponse responseStatus responseHeaders (mapf entity)
withCustomNegotiation :: GenericApplication NegotiatedResponse -> GenericApplication Response
withCustomNegotiation inner req respond = inner req processNegotiated
where
processNegotiated :: NegotiatedResponse -> IO ResponseReceived
processNegotiated (NegotiatedResponse responseStatus responseHeaders responses) =
let
acceptedMediaTypes = fmap fst responses
respondUsing (mediaType, payload) =
let
newHeaders = addOrReplaceHeader responseHeaders (hContentType, mediaType)
response = responseLBS responseStatus newHeaders payload
in respond response
in
case lookup hAccept $ requestHeaders req of
Nothing -> respondUsing $ head responses
Just "*/*" -> respondUsing $ head responses
Just accept -> case matchAccept acceptedMediaTypes accept of
Nothing -> reject' $ notAcceptableRejection acceptedMediaTypes
Just accepted -> respondUsing $ fromJust $ find (\(k, _) -> k == accepted) responses
withCustomNegotiation' :: [ByteString] -> GenericApplication NegotiatedResponse -> GenericApplication Response
withCustomNegotiation' accepted inner req =
let
doit = withCustomNegotiation inner req
in
case lookup hAccept $ requestHeaders req of
Nothing -> doit
Just "*/*" -> doit
Just accept -> case matchAccept accepted accept of
Nothing -> reject $ notAcceptableRejection accepted
Just _ -> doit
notAcceptableRejection :: [ByteString] -> Rejection
notAcceptableRejection acceptedResponses =
Rejection
{ status = notAcceptable406
, message = [i|#{statusMessage notAcceptable406}: Acceptable media types: #{LBC.intercalate ", " acceptedResponses}|]
, priority = 200
, headers = []
}
negotiated :: [(ByteString, a -> LBS.ByteString)] -> EntityResponse a -> NegotiatedResponse
negotiated accptableResponses (EntityResponse responseStatus responseHeaders entity) =
NegotiatedResponse responseStatus responseHeaders (fmap (\(key, v) -> (key, v entity)) accptableResponses)
requestEntity :: [(ByteString, LBS.ByteString -> Either String a)] -> (a -> GenericApplication b) -> GenericApplication b
requestEntity mappings fa req respond =
let
contentTypeHeader = fromMaybe "application/octet-stream" $ lookup hContentType $ requestHeaders req
in
case mapAccept mappings contentTypeHeader of
Just decodeFunc -> do
decodedOrError <- decodeFunc <$> strictRequestBody req
case decodedOrError of
Left decodeError -> reject' $ decodeErrorRejection decodeError
Right decoded -> fa decoded req respond
Nothing -> reject' $ unsupportedMediaTypeRejection $ fmap fst mappings
decodeErrorRejection :: String -> Rejection
decodeErrorRejection reason =
Rejection
{ status = badRequest400
, message = [i|#{statusMessage badRequest400}: Error reading entity: #{reason}|]
, priority = 200
, headers = []
}
unsupportedMediaTypeRejection :: [ByteString] -> Rejection
unsupportedMediaTypeRejection supportedMediaTypes =
Rejection
{ status = unsupportedMediaType415
, message = [i|#{statusMessage unsupportedMediaType415}: Supported Media Types: #{LBC.intercalate ", " supportedMediaTypes}|]
, priority = 200
, headers = []
}
ok :: a -> EntityResponse a
ok = EntityResponse ok200 []
created :: a -> EntityResponse a
created = EntityResponse created201 []
notFound :: a -> EntityResponse a
notFound = EntityResponse notFound404 []
badRequest :: a -> EntityResponse a
badRequest = EntityResponse badRequest400 []
entityResponse :: Status -> ResponseHeaders -> a -> EntityResponse a
entityResponse = EntityResponse