module Network.HTTP.Lucu.Resource
(
Resource(..)
, Rsrc
, FormData(..)
, getConfig
, getRemoteAddr
, getRemoteAddr'
, getRemoteHost
#if defined(HAVE_SSL)
, getRemoteCertificate
#endif
, getRequest
, getMethod
, getRequestURI
, getRequestVersion
, getResourcePath
, getPathInfo
, getQueryForm
, getHeader
, getAccept
, getAcceptEncoding
, isEncodingAcceptable
, getContentType
, getAuthorization
, foundEntity
, foundETag
, foundTimeStamp
, foundNoEntity
, foundNoEntity'
, getChunk
, getChunks
, getForm
, setStatus
, redirect
, setContentType
, setContentEncoding
, setWWWAuthenticate
, setLocation
, setHeader
, deleteHeader
, putChunk
, putChunks
, putBuilder
)
where
import Blaze.ByteString.Builder (Builder)
import qualified Blaze.ByteString.Builder as BB
import qualified Blaze.ByteString.Builder.Internal as BB
import Control.Applicative
import Control.Arrow
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Unicode
import Data.Ascii (Ascii, CIAscii, AsciiBuilder)
import Data.Attempt
import qualified Data.Attoparsec.Char8 as P
import Data.ByteString (ByteString)
import qualified Data.ByteString as Strict
import qualified Data.ByteString.Lazy as Lazy
import Data.Collections
import Data.Convertible.Base
import Data.Convertible.Instances.Text ()
import Data.Convertible.Utils
import Data.Default
import Data.List (intersperse, sort)
import Data.Maybe
import Data.Monoid
import Data.Monoid.Unicode
import Data.Tagged
import Data.Text (Text)
import Data.Time
import Data.Time.Format.HTTP
import Network.HTTP.Lucu.Abortion
import Network.HTTP.Lucu.Authentication
import Network.HTTP.Lucu.Config
import Network.HTTP.Lucu.ContentCoding
import Network.HTTP.Lucu.ETag
import qualified Network.HTTP.Lucu.Headers as H
import Network.HTTP.Lucu.HttpVersion
import Network.HTTP.Lucu.Interaction
import Network.HTTP.Lucu.MultipartForm
import Network.HTTP.Lucu.Parser
import Network.HTTP.Lucu.Request
import Network.HTTP.Lucu.Resource.Internal
import Network.HTTP.Lucu.Response
import Network.HTTP.Lucu.Response.StatusCode
import Network.HTTP.Lucu.MIMEType
import Network.HTTP.Lucu.Utils
import Network.Socket hiding (accept)
import Network.URI hiding (path)
import Prelude hiding (any, drop, lookup, reverse)
import Prelude.Unicode
getRemoteAddr' ∷ Rsrc HostName
getRemoteAddr' = liftIO ∘ toNM =≪ getRemoteAddr
where
toNM ∷ SockAddr → IO HostName
toNM = (fromJust ∘ fst <$>) ∘ getNameInfo [NI_NUMERICHOST] True False
getRemoteHost ∷ Rsrc (Maybe HostName)
getRemoteHost = liftIO ∘ getHN =≪ getRemoteAddr
where
getHN ∷ SockAddr → IO (Maybe HostName)
getHN = (fst <$>) ∘ getNameInfo [] True False
getMethod ∷ Rsrc Method
getMethod = reqMethod <$> getRequest
getRequestURI ∷ Rsrc URI
getRequestURI = reqURI <$> getRequest
getRequestVersion ∷ Rsrc HttpVersion
getRequestVersion = reqVersion <$> getRequest
getPathInfo ∷ Rsrc [Strict.ByteString]
getPathInfo = do rsrcPath ← getResourcePath
reqPath ← uriPathSegments <$> getRequestURI
return $ drop (length rsrcPath) reqPath
getQueryForm ∷ Rsrc [(Strict.ByteString, FormData)]
getQueryForm = parse' <$> getRequestURI
where
parse' = map toPairWithFormData ∘
parseWWWFormURLEncoded ∘
convertUnsafe ∘
drop 1 ∘
uriQuery
toPairWithFormData ∷ (ByteString, ByteString) → (Strict.ByteString, FormData)
toPairWithFormData (name, value)
= let fd = FormData {
fdFileName = Nothing
, fdMIMEType = [mimeType| text/plain |]
, fdContent = Lazy.fromChunks [value]
}
in (name, fd)
getHeader ∷ CIAscii → Rsrc (Maybe Ascii)
getHeader name
= H.getHeader name <$> getRequest
getAccept ∷ Rsrc [MIMEType]
getAccept
= do acceptM ← getHeader "Accept"
case acceptM of
Nothing
→ return []
Just accept
→ case P.parseOnly (finishOff def) (cs accept) of
Right xs → return xs
Left _ → abort $ mkAbortion' BadRequest
$ "Unparsable Accept: " ⊕ cs accept
getAcceptEncoding ∷ Rsrc [(CIAscii, Maybe Double)]
getAcceptEncoding
= do accEncM ← getHeader "Accept-Encoding"
case accEncM of
Nothing
→ do ver ← getRequestVersion
case ver of
HttpVersion 1 0 → return [("identity", Nothing)]
HttpVersion 1 1 → return [("*" , Nothing)]
_ → abort $ mkAbortion' InternalServerError
"getAcceptEncoding: unknown HTTP version"
Just ae
→ if ae ≡ "" then
return [("identity", Nothing)]
else
case P.parseOnly (finishOff def) (cs ae) of
Right xs → return $ map toTuple $ reverse $ sort xs
Left _ → abort $ mkAbortion' BadRequest
$ "Unparsable Accept-Encoding: " ⊕ cs ae
where
toTuple (AcceptEncoding {..})
= (aeEncoding, aeQValue)
isEncodingAcceptable ∷ CIAscii → Rsrc Bool
isEncodingAcceptable encoding = any doesMatch <$> getAcceptEncoding
where
doesMatch ∷ (CIAscii, Maybe Double) → Bool
doesMatch (e, q) = (e ≡ "*" ∨ e ≡ encoding) ∧ q ≢ Just 0
getContentType ∷ Rsrc (Maybe MIMEType)
getContentType
= do cTypeM ← getHeader "Content-Type"
case cTypeM of
Nothing
→ return Nothing
Just cType
→ case P.parseOnly (finishOff def) (cs cType) of
Right t → return $ Just t
Left _ → abort $ mkAbortion' BadRequest
$ "Unparsable Content-Type: " ⊕ cs cType
getAuthorization ∷ Rsrc (Maybe AuthCredential)
getAuthorization
= do authM ← getHeader "Authorization"
case authM of
Nothing
→ return Nothing
Just auth
→ case P.parseOnly (finishOff def) (cs auth) of
Right ac → return $ Just ac
Left _ → return Nothing
foundEntity ∷ ETag → UTCTime → Rsrc ()
foundEntity tag timeStamp
= do driftTo ExaminingRequest
method ← getMethod
when (method ≡ GET ∨ method ≡ HEAD)
$ setHeader "Last-Modified"
$ formatUTCTime timeStamp
when (method ≡ POST)
$ abort
$ mkAbortion' InternalServerError
"foundEntity: this is a POST request."
foundETag tag
driftTo ReceivingBody
foundETag ∷ ETag → Rsrc ()
foundETag tag
= do driftTo ExaminingRequest
method ← getMethod
when (method ≡ GET ∨ method ≡ HEAD)
$ setHeader "ETag"
$ cs tag
when (method ≡ POST)
$ abort
$ mkAbortion' InternalServerError
"Illegal computation of foundETag for POST request."
ifMatch ← getHeader "If-Match"
case ifMatch of
Nothing
→ return ()
Just value
→ if value ≡ "*" then
return ()
else
case P.parseOnly (finishOff def) (cs value) of
Right []
→ abort $ mkAbortion' BadRequest
$ "Empty If-Match"
Right tags
→ when ((¬) (any (≡ tag) tags))
$ abort
$ mkAbortion' PreconditionFailed
$ "The entity tag doesn't match: " ⊕ cs value
Left _
→ abort $ mkAbortion' BadRequest
$ "Unparsable If-Match: " ⊕ cs value
let statusForNoneMatch
= if method ≡ GET ∨ method ≡ HEAD then
fromStatusCode NotModified
else
fromStatusCode PreconditionFailed
ifNoneMatch ← getHeader "If-None-Match"
case ifNoneMatch of
Nothing
→ return ()
Just value
→ if value ≡ "*" then
abort $ mkAbortion' statusForNoneMatch
$ "The entity tag matches: *"
else
case P.parseOnly (finishOff def) (cs value) of
Right []
→ abort $ mkAbortion' BadRequest
$ "Empty If-None-Match"
Right tags
→ when (any (≡ tag) tags)
$ abort
$ mkAbortion' statusForNoneMatch
$ "The entity tag matches: " ⊕ cs value
Left _
→ abort $ mkAbortion' BadRequest
$ "Unparsable If-None-Match: " ⊕ cs value
driftTo ReceivingBody
foundTimeStamp ∷ UTCTime → Rsrc ()
foundTimeStamp timeStamp
= do driftTo ExaminingRequest
method ← getMethod
when (method ≡ GET ∨ method ≡ HEAD)
$ setHeader "Last-Modified"
$ formatUTCTime timeStamp
when (method ≡ POST)
$ abort
$ mkAbortion' InternalServerError
"Illegal call of foundTimeStamp for POST request."
let statusForIfModSince
= if method ≡ GET ∨ method ≡ HEAD then
fromStatusCode NotModified
else
fromStatusCode PreconditionFailed
ifModSince ← getHeader "If-Modified-Since"
case ifModSince of
Just str → case untag' <$> (fromAttempt $ ca str) of
Just lastTime
→ when (timeStamp ≤ lastTime)
$ abort
$ mkAbortion' statusForIfModSince
$ "The entity has not been modified since " ⊕ cs str
Nothing
→ abort $ mkAbortion' BadRequest
$ "Malformed If-Modified-Since: " ⊕ cs str
Nothing → return ()
ifUnmodSince ← getHeader "If-Unmodified-Since"
case ifUnmodSince of
Just str → case untag' <$> (fromAttempt $ ca str) of
Just lastTime
→ when (timeStamp > lastTime)
$ abort
$ mkAbortion' PreconditionFailed
$ "The entity has not been modified since " ⊕ cs str
Nothing
→ abort $ mkAbortion' BadRequest
$ "Malformed If-Unmodified-Since: " ⊕ cs str
Nothing → return ()
driftTo ReceivingBody
where
untag' ∷ Tagged HTTP α → α
untag' = untag
foundNoEntity ∷ Maybe Text → Rsrc ()
foundNoEntity msgM
= do driftTo ExaminingRequest
method ← getMethod
when (method ≢ PUT)
$ abort
$ mkAbortion NotFound [] msgM
ifMatch ← getHeader "If-Match"
when (ifMatch ≢ Nothing)
$ abort
$ mkAbortion PreconditionFailed [] msgM
driftTo ReceivingBody
foundNoEntity' ∷ Rsrc ()
foundNoEntity' = foundNoEntity Nothing
getChunks ∷ Maybe Int → Rsrc Lazy.ByteString
getChunks (Just n)
| n < 0 = fail ("getChunks: limit must not be negative: " ⧺ show n)
| n ≡ 0 = return (∅)
| otherwise = getChunks' n
getChunks Nothing
= getConfig ≫= getChunks ∘ Just ∘ cnfMaxEntityLength
getChunks' ∷ Int → Rsrc Lazy.ByteString
getChunks' limit = go limit (∅)
where
go ∷ Int → Builder → Rsrc Lazy.ByteString
go 0 _ = do chunk ← getChunk 1
if Strict.null chunk then
return (∅)
else
abort $ mkAbortion' RequestEntityTooLarge
$ "Request body must be smaller than "
⊕ cs (show limit)
⊕ " bytes."
go !n !b = do c ← getChunk $ min n BB.defaultBufferSize
if Strict.null c then
return $ BB.toLazyByteString b
else
do let n' = n Strict.length c
xs' = b ⊕ BB.fromByteString c
go n' xs'
getForm ∷ Maybe Int → Rsrc [(Strict.ByteString, FormData)]
getForm limit
= do cTypeM ← getContentType
case cTypeM of
Nothing
→ abort $ mkAbortion' BadRequest "Missing Content-Type"
Just (MIMEType "application" "x-www-form-urlencoded" _)
→ readWWWFormURLEncoded
Just (MIMEType "multipart" "form-data" params)
→ readMultipartFormData params
Just cType
→ abort $ mkAbortion' UnsupportedMediaType
$ cs
$ ("Unsupported media type: " ∷ Ascii)
⊕ cs cType
where
readWWWFormURLEncoded
= (map toPairWithFormData ∘ parseWWWFormURLEncoded)
<$>
(bsToAscii =≪ getChunks limit)
bsToAscii bs
= case convertAttemptVia ((⊥) ∷ ByteString) bs of
Success a → return a
Failure e → abort $ mkAbortion' BadRequest $ cs (show e)
readMultipartFormData m
= case lookup "boundary" m of
Nothing
→ abort $ mkAbortion' BadRequest "Missing boundary of multipart/form-data"
Just boundary
→ do src ← getChunks limit
b ← case ca boundary of
Success b → return b
Failure _ → abort $ mkAbortion' BadRequest
$ "Malformed boundary: " ⊕ boundary
case parseMultipartFormData b src of
Right xs → return $ map (first cs) xs
Left err → abort $ mkAbortion' BadRequest $ cs err
redirect ∷ StatusCode sc ⇒ sc → URI → Rsrc ()
redirect (fromStatusCode → sc) uri
= do when (sc ≡ cs NotModified ∨ (¬) (isRedirection sc))
$ abort
$ mkAbortion' InternalServerError
$ cs
$ ("Attempted to redirect with status " ∷ Ascii)
⊕ cs sc
setStatus sc
setLocation uri
setContentType ∷ MIMEType → Rsrc ()
setContentType = setHeader "Content-Type" ∘ cs
setLocation ∷ URI → Rsrc ()
setLocation uri
= case ca uriStr of
Success a → setHeader "Location" a
Failure e → abort $ mkAbortion' InternalServerError
$ cs (show e)
where
uriStr = uriToString id uri ""
setContentEncoding ∷ [CIAscii] → Rsrc ()
setContentEncoding codings
= do ver ← getRequestVersion
tr ← case ver of
HttpVersion 1 0 → return (toAB ∘ unnormalizeCoding)
HttpVersion 1 1 → return toAB
_ → abort $ mkAbortion' InternalServerError
"setContentEncoding: Unknown HTTP version"
setHeader "Content-Encoding"
$ cs
$ mconcat
$ intersperse (cs (", " ∷ Ascii))
$ map tr codings
where
toAB ∷ ConvertSuccess α AsciiBuilder ⇒ α → AsciiBuilder
toAB = cs
setWWWAuthenticate ∷ AuthChallenge → Rsrc ()
setWWWAuthenticate = setHeader "WWW-Authenticate" ∘ cs
putChunk ∷ Strict.ByteString → Rsrc ()
putChunk = putBuilder ∘ BB.fromByteString
putChunks ∷ Lazy.ByteString → Rsrc ()
putChunks = putBuilder ∘ BB.fromLazyByteString