]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Postprocess.hs
Still working on Postprocess...
[Lucu.git] / Network / HTTP / Lucu / Postprocess.hs
index 989ad164707ca9afb99f94f55dcc69fe2840e658..49c95e809be046489bed306c83db6f77eab12baf 100644 (file)
@@ -1,5 +1,6 @@
 {-# LANGUAGE
     BangPatterns
+  , DoAndIfThenElse
   , OverloadedStrings
   , UnicodeSyntax
   #-}
@@ -9,27 +10,28 @@ module Network.HTTP.Lucu.Postprocess
     )
     where
 import Control.Applicative
-import           Control.Concurrent.STM
-import           Control.Monad
+import Control.Concurrent.STM
+import Control.Monad
 import Control.Monad.Unicode
 import Data.Ascii (Ascii, CIAscii)
 import qualified Data.Ascii as A
 import qualified Data.ByteString as Strict (ByteString)
 import qualified Data.ByteString.Char8 as C8 hiding (ByteString)
-import           Data.IORef
-import           Data.Maybe
-import           Data.Time
+import Data.IORef
+import Data.Maybe
+import Data.Monoid.Unicode
+import Data.Time
 import qualified Data.Time.HTTP as HTTP
-import           GHC.Conc (unsafeIOToSTM)
-import           Network.HTTP.Lucu.Abortion
-import           Network.HTTP.Lucu.Config
-import           Network.HTTP.Lucu.Headers
-import           Network.HTTP.Lucu.HttpVersion
-import           Network.HTTP.Lucu.Interaction
-import           Network.HTTP.Lucu.Request
-import           Network.HTTP.Lucu.Response
+import GHC.Conc (unsafeIOToSTM)
+import Network.HTTP.Lucu.Abortion
+import Network.HTTP.Lucu.Config
+import Network.HTTP.Lucu.Headers
+import Network.HTTP.Lucu.HttpVersion
+import Network.HTTP.Lucu.Interaction
+import Network.HTTP.Lucu.Request
+import Network.HTTP.Lucu.Response
 import Prelude.Unicode
-import           System.IO.Unsafe
+import System.IO.Unsafe
 
 {-
   
@@ -71,17 +73,24 @@ postprocess !itr
          let sc = resStatus res
 
          unless (any (\ p → p sc) [isSuccessful, isRedirection, isError])
-                  $ abortSTM InternalServerError []
-                        $ Just ("The status code is not good for a final status: "
-                                ++ show sc)
-
-         when (sc ≡ MethodNotAllowed ∧ getHeader (C8.pack "Allow") res ≡ Nothing)
-                  $ abortSTM InternalServerError []
-                        $ Just ("The status was " ++ show sc ++ " but no Allow header.")
-
-         when (sc /= NotModified ∧ isRedirection sc ∧ getHeader (C8.pack "Location") res ≡ Nothing)
-                  $ abortSTM InternalServerError []
-                        $ Just ("The status code was " ++ show sc ++ " but no Location header.")
+             $ abortSTM InternalServerError []
+             $ Just
+             $ A.toText ( "The status code is not good for a final status of a response: "
+                          ⊕ printStatusCode sc )
+
+         when (sc ≡ MethodNotAllowed ∧ getHeader "Allow" res ≡ Nothing)
+             $ abortSTM InternalServerError []
+             $ Just
+             $ A.toText ( "The status was "
+                          ⊕ printStatusCode sc
+                          ⊕ " but no Allow header." )
+
+         when (sc /= NotModified ∧ isRedirection sc ∧ getHeader "Location" res ≡ Nothing)
+             $ abortSTM InternalServerError []
+             $ Just
+             $ A.toText ( "The status code was "
+                          ⊕ printStatusCode sc
+                          ⊕ " but no Location header." )
 
          when (reqM /= Nothing) relyOnRequest
 
@@ -115,32 +124,34 @@ postprocess !itr
 
                if canHaveBody then
                    when (reqVer ≡ HttpVersion 1 1)
-                            $ do updateRes $ setHeader "Transfer-Encoding" "chunked"
-                                 writeItr itr itrWillChunkBody True
-                 else
+                       $ do updateRes $ setHeader "Transfer-Encoding" "chunked"
+                            writeItr itr itrWillChunkBody True
+               else
                    -- body 関連のヘッダを削除。但し HEAD なら Content-* は殘す
                    when (reqMethod req /= HEAD)
-                            $ do updateRes $ deleteHeader "Content-Type"
-                                 updateRes $ deleteHeader "Etag"
-                                 updateRes $ deleteHeader "Last-Modified"
+                       $ do updateRes $ deleteHeader "Content-Type"
+                            updateRes $ deleteHeader "Etag"
+                            updateRes $ deleteHeader "Last-Modified"
 
                conn ← readHeader "Connection"
                case conn of
                  Nothing    → return ()
                  Just value → when (A.toCIAscii value ≡ "close")
-                                   $ writeItr itr itrWillClose True
+                                  $ writeItr itr itrWillClose True
 
                willClose ← readItr itr itrWillClose id
                when willClose
-                        $ updateRes $ setHeader "Connection" "close"
+                   $ updateRes $ setHeader "Connection" "close"
 
                when (reqMethod req ≡ HEAD ∨ not canHaveBody)
-                        $ writeTVar (itrWillDiscardBody itr) True
+                   $ writeTVar (itrWillDiscardBody itr) True
 
       readHeader ∷ CIAscii → STM (Maybe Ascii)
+      {-# INLINE readHeader #-}
       readHeader = readItr itr itrResponse ∘ getHeader
 
       updateRes ∷ (Response → Response) → STM ()
+      {-# INLINE updateRes #-}
       updateRes = updateItr itr itrResponse
 
 completeUnconditionalHeaders ∷ Config → Response → IO Response