template-haskell == 2.5.*,
text == 0.11.*,
time == 1.2.*,
- time-http == 0.4.*,
+ time-http == 0.5.*,
transformers == 0.2.*
if flag(ssl)
, mkInteractionQueue
, getCurrentDate
+ , formatUTCTime
)
where
import Blaze.ByteString.Builder (Builder)
import Data.ByteString (ByteString)
import Data.Convertible.Base
import Data.Monoid.Unicode
-import Data.Proxy
import Data.Sequence (Seq)
+import Data.Tagged
import Data.Time
import Data.Time.Format.HTTP
import Data.Typeable
getCurrentDate ∷ IO Ascii
{-# INLINE getCurrentDate #-}
-getCurrentDate = flip proxy http ∘ cs <$> getCurrentTime
+getCurrentDate = formatUTCTime <$> getCurrentTime
+
+formatUTCTime ∷ UTCTime → Ascii
+{-# INLINE formatUTCTime #-}
+formatUTCTime = cs' ∘ Tagged
+ where
+ cs' ∷ Tagged HTTP UTCTime → Ascii
+ cs' = cs
req' = updateAuthority host port req
in
setRequest req'
- -- HTTP/1.1 requests MUST have a Host header.
+ -- HTTP/1.1 requests MUST have a Host header, but if
+ -- the requested URI has an authority, the value of
+ -- Host header must be ignored. See:
+ -- http://tools.ietf.org/html/rfc2616#section-5.2
HttpVersion 1 1
→ case getHeader "Host" req of
Just str
- → let (host, port)
- = parseHost str
- req' = updateAuthority host port req
- in
- setRequest req'
+ | isNothing ∘ uriAuthority ∘ reqURI $ req
+ → let (host, port)
+ = parseHost str
+ req' = updateAuthority host port req
+ in
+ setRequest req'
+ | otherwise
+ → return ()
Nothing
→ setStatus BadRequest
-- Should never reach here...
(hText, pAscii)
updateAuthority ∷ CI Text → Ascii → Request → Request
-updateAuthority host port req
- = let uri = reqURI req
- uri' = uri {
+updateAuthority host port req@(Request {..})
+ = let uri' = reqURI {
uriAuthority = Just URIAuth {
uriUserInfo = ""
, uriRegName = cs $ CI.original host
import Data.Maybe
import Data.Monoid
import Data.Monoid.Unicode
-import Data.Proxy
import Data.Tagged
import Data.Text (Text)
import Data.Time
method ← getMethod
when (method ≡ GET ∨ method ≡ HEAD)
$ setHeader "Last-Modified"
- $ flip proxy http
- $ cs timeStamp
+ $ formatUTCTime timeStamp
when (method ≡ POST)
$ abort
$ mkAbortion' InternalServerError
method ← getMethod
when (method ≡ GET ∨ method ≡ HEAD)
$ setHeader "Last-Modified"
- $ flip proxy http
- $ cs timeStamp
+ $ formatUTCTime timeStamp
when (method ≡ POST)
$ abort
$ mkAbortion' InternalServerError
ifModSince ← getHeader "If-Modified-Since"
case ifModSince of
- Just str → case fromAttempt $ ca (Tagged str ∷ Tagged HTTP Ascii) of
+ Just str → case untag' <$> (fromAttempt $ ca str) of
Just lastTime
→ when (timeStamp ≤ lastTime)
$ abort
ifUnmodSince ← getHeader "If-Unmodified-Since"
case ifUnmodSince of
- Just str → case fromAttempt $ ca (Tagged str ∷ Tagged HTTP Ascii) of
+ Just str → case untag' <$> (fromAttempt $ ca str) of
Just lastTime
→ when (timeStamp > lastTime)
$ abort
Nothing → return ()
driftTo ReceivingBody
+ where
+ untag' ∷ Tagged HTTP α → α
+ {-# INLINE untag' #-}
+ untag' = untag
-- |@'foundNoEntity' mStr@ tells the system that the 'Rsrc' found no
-- entity for the request URI. @mStr@ is an optional error message to