]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Postprocess.hs
Many changes...
[Lucu.git] / Network / HTTP / Lucu / Postprocess.hs
index 1a00b00b0eab578bca9db5d52e3e6bf4003abf46..4950a0b97006e29b00446a9a6cfbf8ee90ea1781 100644 (file)
@@ -1,6 +1,7 @@
 {-# LANGUAGE
     DoAndIfThenElse
   , OverloadedStrings
+  , RecordWildCards
   , UnicodeSyntax
   #-}
 module Network.HTTP.Lucu.Postprocess
@@ -14,7 +15,6 @@ import Control.Monad
 import Control.Monad.Unicode
 import Data.Ascii (Ascii, CIAscii)
 import qualified Data.Ascii as A
-import Data.Maybe
 import Data.Monoid.Unicode
 import Data.Time
 import qualified Data.Time.HTTP as HTTP
@@ -29,6 +29,8 @@ import Network.HTTP.Lucu.Response
 import Prelude.Unicode
 
 {-
+  TODO: Tanslate this memo into English. It doesn't make sense to
+  non-Japanese speakers.
   
   * Response が未設定なら、200 OK にする。
 
@@ -62,9 +64,8 @@ import Prelude.Unicode
 -}
 
 postprocess ∷ Interaction → STM ()
-postprocess itr
-    = do reqM ← readItr itrRequest  itr
-         res  ← readItr itrResponse itr
+postprocess (Interaction {..})
+    = do res  ← readTVar itrResponse
          let sc = resStatus res
 
          unless (any (\ p → p sc) [isSuccessful, isRedirection, isError])
@@ -93,28 +94,27 @@ postprocess itr
              ⊕ printStatusCode sc
              ⊕ A.toAsciiBuilder " but no Location header."
 
-         when (reqM ≢ Nothing) relyOnRequest
+         reqM ← readTVar itrRequest
+         case reqM of
+           Just req → postprocessWithRequest sc req
+           Nothing  → return ()
 
          -- itrResponse の内容は relyOnRequest によって變へられてゐる可
          -- 能性が高い。
-         do oldRes ← readItr itrResponse itr
+         do oldRes ← readTVar itrResponse
             newRes ← unsafeIOToSTM
-                     $ completeUnconditionalHeaders (itrConfig itr) oldRes
-            writeItr itrResponse newRes itr
+                     $ completeUnconditionalHeaders itrConfig oldRes
+            writeTVar itrResponse newRes
     where
-      relyOnRequest ∷ STM ()
-      relyOnRequest
-          = do status ← resStatus <$> readItr itrResponse itr
-               req    ← fromJust  <$> readItr itrRequest  itr
-
-               let reqVer      = reqVersion req
-                   canHaveBody = if reqMethod req ≡ HEAD then
+      postprocessWithRequest ∷ StatusCode → Request → STM ()
+      postprocessWithRequest sc (Request {..})
+          = do let canHaveBody = if reqMethod ≡ HEAD then
                                      False
                                  else
-                                     not (isInformational status ∨
-                                          status ≡ NoContent     ∨
-                                          status ≡ ResetContent  ∨
-                                          status ≡ NotModified   )
+                                     (¬) (isInformational sc ∨
+                                          sc ≡ NoContent     ∨
+                                          sc ≡ ResetContent  ∨
+                                          sc ≡ NotModified   )
 
                updateRes $ deleteHeader "Content-Length"
                updateRes $ deleteHeader "Transfer-Encoding"
@@ -124,36 +124,42 @@ postprocess itr
                         $ updateRes $ setHeader "Content-Type" defaultPageContentType
 
                if canHaveBody then
-                   when (reqVer ≡ HttpVersion 1 1)
+                   when (reqVersion ≡ HttpVersion 1 1)
                        $ do updateRes $ setHeader "Transfer-Encoding" "chunked"
-                            writeItr itrWillChunkBody True itr
+                            writeTVar itrWillChunkBody True
                else
                    -- body 関連のヘッダを削除。但し HEAD なら Content-* は殘す
-                   when (reqMethod req ≢ HEAD)
+                   when (reqMethod ≢ HEAD)
                        $ do updateRes $ deleteHeader "Content-Type"
                             updateRes $ deleteHeader "Etag"
                             updateRes $ deleteHeader "Last-Modified"
 
-               conn ← readHeader "Connection"
+               conn ← readCIHeader "Connection"
                case conn of
                  Nothing    → return ()
-                 Just value → when (A.toCIAscii value ≡ "close")
-                                  $ writeItr itrWillClose True itr
+                 Just value → when (value ≡ "close")
+                                  $ writeTVar itrWillClose True
 
-               willClose ← readItr itrWillClose itr
+               willClose ← readTVar itrWillClose
                when willClose
                    $ updateRes $ setHeader "Connection" "close"
 
-               when (reqMethod req ≡ HEAD ∨ not canHaveBody)
-                   $ writeTVar (itrWillDiscardBody itr) True
+               when (reqMethod ≡ HEAD ∨ not canHaveBody)
+                   $ writeTVar itrWillDiscardBody True
 
       readHeader ∷ CIAscii → STM (Maybe Ascii)
       {-# INLINE readHeader #-}
-      readHeader k = getHeader k <$> readItr itrResponse itr
+      readHeader k = getHeader k <$> readTVar itrResponse
+
+      readCIHeader ∷ CIAscii → STM (Maybe CIAscii)
+      {-# INLINE readCIHeader #-}
+      readCIHeader k = getCIHeader k <$> readTVar itrResponse
 
       updateRes ∷ (Response → Response) → STM ()
       {-# INLINE updateRes #-}
-      updateRes f = updateItr itrResponse f itr
+      updateRes f
+          = do old ← readTVar itrResponse
+               writeTVar itrResponse (f old)
 
 completeUnconditionalHeaders ∷ Config → Response → IO Response
 completeUnconditionalHeaders conf = (compDate =≪) ∘ compServer