X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FResource.hs;h=520502204df5d933484d85298115051574915dd3;hb=3b448555e621530c3483f03b4b5156dc606b2035;hp=a970b46f9f695595f435793768c2285b51221490;hpb=bb41be0c967538a1014c87103a3a5d3840ad3e15;p=Lucu.git diff --git a/Network/HTTP/Lucu/Resource.hs b/Network/HTTP/Lucu/Resource.hs index a970b46..5205022 100644 --- a/Network/HTTP/Lucu/Resource.hs +++ b/Network/HTTP/Lucu/Resource.hs @@ -1,12 +1,14 @@ {-# LANGUAGE CPP , BangPatterns + , FlexibleContexts , GeneralizedNewtypeDeriving , DoAndIfThenElse , OverloadedStrings , QuasiQuotes , RecordWildCards , UnicodeSyntax + , ViewPatterns #-} -- |This is the Resource Monad; monadic actions to define a behavior -- of resource. The 'Rsrc' Monad is a kind of 'IO' Monad thus it @@ -147,8 +149,7 @@ import Control.Arrow import Control.Monad import Control.Monad.IO.Class import Control.Monad.Unicode -import Data.Ascii (Ascii, CIAscii) -import qualified Data.Ascii as A +import Data.Ascii (Ascii, CIAscii, AsciiBuilder) import Data.Attempt import qualified Data.Attoparsec.Char8 as P import Data.ByteString (ByteString) @@ -158,14 +159,13 @@ 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.Proxy import Data.Tagged import Data.Text (Text) -import qualified Data.Text as T import Data.Time import Data.Time.Format.HTTP import Network.HTTP.Lucu.Abortion @@ -181,9 +181,8 @@ 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.MIMEType (MIMEType(..)) -import qualified Network.HTTP.Lucu.MIMEType as MT -import Network.HTTP.Lucu.MIMEType.TH +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) @@ -266,7 +265,7 @@ getAccept Nothing → return [] Just accept - → case P.parseOnly (finishOff MT.mimeTypeList) (cs accept) of + → case P.parseOnly (finishOff def) (cs accept) of Right xs → return xs Left _ → abort $ mkAbortion' BadRequest $ "Unparsable Accept: " ⊕ cs accept @@ -294,7 +293,7 @@ getAcceptEncoding -- identity のみが許される。 return [("identity", Nothing)] else - case P.parseOnly (finishOff acceptEncodingList) (cs ae) of + 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 @@ -318,7 +317,7 @@ getContentType Nothing → return Nothing Just cType - → case P.parseOnly (finishOff MT.mimeType) (cs cType) of + → case P.parseOnly (finishOff def) (cs cType) of Right t → return $ Just t Left _ → abort $ mkAbortion' BadRequest $ "Unparsable Content-Type: " ⊕ cs cType @@ -332,7 +331,7 @@ getAuthorization Nothing → return Nothing Just auth - → case P.parseOnly (finishOff authCredential) (cs auth) of + → case P.parseOnly (finishOff def) (cs auth) of Right ac → return $ Just ac Left _ → return Nothing @@ -357,8 +356,7 @@ foundEntity tag timeStamp method ← getMethod when (method ≡ GET ∨ method ≡ HEAD) $ setHeader "Last-Modified" - $ flip proxy http - $ cs timeStamp + $ formatUTCTime timeStamp when (method ≡ POST) $ abort $ mkAbortion' InternalServerError @@ -395,7 +393,10 @@ foundETag tag → if value ≡ "*" then return () else - case P.parseOnly (finishOff eTagList) (cs value) of + case P.parseOnly (finishOff def) (cs value) of + Right [] + → abort $ mkAbortion' BadRequest + $ "Empty If-Match" Right tags -- tags の中に一致するものが無ければ -- PreconditionFailed で終了。 @@ -423,7 +424,10 @@ foundETag tag abort $ mkAbortion' statusForNoneMatch $ "The entity tag matches: *" else - case P.parseOnly (finishOff eTagList) (cs value) of + case P.parseOnly (finishOff def) (cs value) of + Right [] + → abort $ mkAbortion' BadRequest + $ "Empty If-None-Match" Right tags → when (any (≡ tag) tags) $ abort @@ -452,8 +456,7 @@ foundTimeStamp timeStamp method ← getMethod when (method ≡ GET ∨ method ≡ HEAD) $ setHeader "Last-Modified" - $ flip proxy http - $ cs timeStamp + $ formatUTCTime timeStamp when (method ≡ POST) $ abort $ mkAbortion' InternalServerError @@ -467,7 +470,7 @@ foundTimeStamp timeStamp 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 @@ -480,7 +483,7 @@ foundTimeStamp timeStamp 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 @@ -492,6 +495,10 @@ foundTimeStamp timeStamp 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 @@ -555,7 +562,7 @@ getChunks' limit = go limit (∅) else abort $ mkAbortion' RequestEntityTooLarge $ "Request body must be smaller than " - ⊕ T.pack (show limit) + ⊕ cs (show limit) ⊕ " bytes." go !n !b = do c ← getChunk $ min n BB.defaultBufferSize if Strict.null c then @@ -613,19 +620,19 @@ getForm limit $ "Malformed boundary: " ⊕ boundary case parseMultipartFormData b src of Right xs → return $ map (first cs) xs - Left err → abort $ mkAbortion' BadRequest $ T.pack err + Left err → abort $ mkAbortion' BadRequest $ cs err -- |@'redirect' code uri@ declares the response status as @code@ and -- \"Location\" header field as @uri@. The @code@ must satisfy -- 'isRedirection' or it raises an error. redirect ∷ StatusCode sc ⇒ sc → URI → Rsrc () -redirect sc uri - = do when (sc ≈ NotModified ∨ (¬) (isRedirection sc)) +redirect (fromStatusCode → sc) uri + = do when (sc ≡ cs NotModified ∨ (¬) (isRedirection sc)) $ abort $ mkAbortion' InternalServerError $ cs $ ("Attempted to redirect with status " ∷ Ascii) - ⊕ cs (fromStatusCode sc) + ⊕ cs sc setStatus sc setLocation uri @@ -639,10 +646,10 @@ setContentType = setHeader "Content-Type" ∘ cs -- @uri@. You usually don't need to call this function directly. setLocation ∷ URI → Rsrc () setLocation uri - = case A.fromChars uriStr of - Just a → setHeader "Location" a - Nothing → abort $ mkAbortion' InternalServerError - $ "Malformed URI: " ⊕ T.pack uriStr + = case ca uriStr of + Success a → setHeader "Location" a + Failure e → abort $ mkAbortion' InternalServerError + $ cs (show e) where uriStr = uriToString id uri "" @@ -657,12 +664,13 @@ setContentEncoding codings _ → abort $ mkAbortion' InternalServerError "setContentEncoding: Unknown HTTP version" setHeader "Content-Encoding" - $ A.fromAsciiBuilder + $ cs $ mconcat - $ intersperse (A.toAsciiBuilder ", ") + $ intersperse (cs (", " ∷ Ascii)) $ map tr codings where - toAB = A.toAsciiBuilder ∘ A.fromCIAscii + toAB ∷ ConvertSuccess α AsciiBuilder ⇒ α → AsciiBuilder + toAB = cs -- |@'setWWWAuthenticate' challenge@ declares the response header -- \"WWW-Authenticate\" as @challenge@.