]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Postprocess.hs
changed everything like a maniac
[Lucu.git] / Network / HTTP / Lucu / Postprocess.hs
index 260bbcc6bdffb3d42efaad0a2560f88c3d719878..732c47a809002e39e08e522f2b5681e508b9143b 100644 (file)
@@ -1,26 +1,36 @@
+{-# LANGUAGE
+    DoAndIfThenElse
+  , OverloadedStrings
+  , RecordWildCards
+  , UnicodeSyntax
+  #-}
 module Network.HTTP.Lucu.Postprocess
-    ( postprocess -- Interaction -> STM ()
-    , completeUnconditionalHeaders -- Config -> Response -> IO Response
+    ( postprocess
+    , completeUnconditionalHeaders
     )
     where
-
-import           Control.Concurrent.STM
-import           Control.Monad
-import           Data.Char
-import           Data.Maybe
-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.RFC1123DateTime
-import           Network.HTTP.Lucu.Request
-import           Network.HTTP.Lucu.Response
-import           Network.HTTP.Lucu.Utils
-import           System.Time
+import Control.Applicative
+import Control.Concurrent.STM
+import Control.Monad
+import Control.Monad.Unicode
+import Data.Ascii (Ascii, CIAscii)
+import qualified Data.Ascii as A
+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 Prelude.Unicode
 
 {-
+  TODO: Tanslate this memo into English. It doesn't make sense to
+  non-Japanese speakers.
   
   * Response が未設定なら、200 OK にする。
 
@@ -31,18 +41,15 @@ import           System.Time
   * 304 Not Modified 以外の 3xx なのに Location ヘッダが無ければ 500 に
     する。
 
-  * Content-Length があれば、それを削除する。
-
-  * HTTP/1.1 であり、且つ body を持つ事が出來る時、Transfer-Encoding の
-    最後の要素が chunked でなければ 500 Internal Error にする。
-    Transfer-Encoding が未設定であれば、chunked に設定する。
+  * Content-Length があれば、それを削除する。Transfer-Encoding があって
+    も削除する。
 
-  * HTTP/1.0 なのに Transfer-Encoding が設定濟なら 500 Internal Server
-    Error にする。但し identity だけは許す
+  * HTTP/1.1 であり、body を持つ事が出來る時、Transfer-Encoding を
+    chunked に設定する
 
-  * body を持つ事が出來る時、Content-Type が無ければ
-    application/octet-stream にする。出來ない時、HEAD でなければ
-    Content-Type, Etag, Last-Modified を削除する。
+  * body を持つ事が出來る時、Content-Type が無ければデフォルト値にする。
+    出來ない時、HEAD でなければContent-Type, Etag, Last-Modified を削除
+    する。
 
   * body を持つ事が出來ない時、body 破棄フラグを立てる。
 
@@ -56,127 +63,116 @@ import           System.Time
 
 -}
 
-postprocess :: Interaction -> STM ()
-postprocess itr
-    = do resM <- readItr itr itrResponse id
-
-         case resM of
-           Nothing  -> writeItr itr itrResponse
-                       $ Just $ Response {
-                               resVersion = HttpVersion 1 1
-                             , resStatus  = Ok
-                             , resHeaders = []
-                             }
-           Just res -> do let sc = resStatus res
-
-                          when (not $ 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 "Allow" res == Nothing)
-                                   $ abortSTM InternalServerError []
-                                         $ Just ("The status was " ++ show sc ++ " but no Allow header.")
-
-                          when (sc /= NotModified && isRedirection sc && getHeader "Location" res == Nothing)
-                                   $ abortSTM InternalServerError []
-                                         $ Just ("The status code was " ++ show sc ++ " but no Location header.")
-
-         when (itrRequest itr /= Nothing)
-              $ relyOnRequest itr
-
-         do oldRes <- readItr itr itrResponse id
-            newRes <- unsafeIOToSTM
-                      $ completeUnconditionalHeaders (itrConfig itr) (fromJust oldRes)
-            writeItr itr itrResponse $ Just newRes
+postprocess ∷ Interaction → STM ()
+postprocess (Interaction {..})
+    = do res  ← readTVar itrResponse
+         let sc = resStatus res
+
+         unless (any (\ p → p sc) [isSuccessful, isRedirection, isError])
+             $ abortSTM InternalServerError []
+             $ Just
+             $ A.toText
+             $ A.fromAsciiBuilder
+             $ A.toAsciiBuilder "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
+             $ A.fromAsciiBuilder
+             $ A.toAsciiBuilder "The status was "
+             ⊕ printStatusCode sc
+             ⊕ A.toAsciiBuilder " but no Allow header."
+
+         when (sc ≢ NotModified ∧ isRedirection sc ∧ getHeader "Location" res ≡ Nothing)
+             $ abortSTM InternalServerError []
+             $ Just
+             $ A.toText
+             $ A.fromAsciiBuilder
+             $ A.toAsciiBuilder "The status code was "
+             ⊕ printStatusCode sc
+             ⊕ A.toAsciiBuilder " but no Location header."
+
+         case itrRequest of
+           Just req → postprocessWithRequest sc req
+           Nothing  → return ()
+
+         -- itrResponse の内容は relyOnRequest によって變へられてゐる可
+         -- 能性が高い。
+         do oldRes ← readTVar itrResponse
+            newRes ← unsafeIOToSTM
+                     $ completeUnconditionalHeaders itrConfig oldRes
+            writeTVar itrResponse newRes
     where
-      relyOnRequest :: Interaction -> STM ()
-      relyOnRequest itr
-          = do status <- readItr itr itrResponse (resStatus . fromJust)
-
-               let req         = fromJust $ itrRequest itr
-                   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"
 
-               updateRes itr $ deleteHeader "Content-Length"
+               cType ← readHeader "Content-Type"
+               when (cType ≡ Nothing)
+                        $ updateRes $ setHeader "Content-Type" defaultPageContentType
 
                if canHaveBody then
-                   do teM <- readHeader itr "Transfer-Encoding"
-                      if reqVer == HttpVersion 1 1 then
-
-                          do case teM of
-                               Nothing -> updateRes itr $ setHeader "Transfer-Encoding" "chunked"
-                               Just te -> let teList = [trim isWhiteSpace x
-                                                            | x <- splitBy (== ',') (map toLower te)]
-                                          in
-                                            when (teList == [] || last teList /= "chunked")
-                                                     $ abortSTM InternalServerError []
-                                                           $ Just ("Transfer-Encoding must end with `chunked' "
-                                                                   ++ "because this is an HTTP/1.1 request: "
-                                                                   ++ te)
-
-                             writeItr itr itrWillChunkBody True
-                        else
-                          case fmap (map toLower) teM of
-                            Nothing         -> return ()
-                            Just "identity" -> return ()
-                            Just te         -> abortSTM InternalServerError []
-                                               $ Just ("Transfer-Encoding must be `identity' because "
-                                                       ++ "this is an HTTP/1.0 request: "
-                                                       ++ te)
-
-                      cType <- readHeader itr "Content-Type"
-                      when (cType == Nothing)
-                               $ updateRes itr $ setHeader "Content-Type" "application/octet-stream"
-                 else
+                   when (reqVersion ≡ HttpVersion 1 1)
+                       $ do updateRes $ setHeader "Transfer-Encoding" "chunked"
+                            writeTVar itrWillChunkBody True
+               else
                    -- body 関連のヘッダを削除。但し HEAD なら Content-* は殘す
-                   do updateRes itr $ deleteHeader "Transfer-Encoding"
-                      when (reqMethod req /= HEAD)
-                               $ do updateRes itr $ deleteHeader "Content-Type"
-                                    updateRes itr $ deleteHeader "Etag"
-                                    updateRes itr $ deleteHeader "Last-Modified"
-
-               conn <- readHeader itr "Connection"
-               case fmap (map toLower) conn of
-                 Just "close" -> writeItr itr itrWillClose True
-                 _            -> return ()
-
-               willClose <- readItr itr itrWillClose id
+                   when (reqMethod ≢ HEAD)
+                       $ do updateRes $ deleteHeader "Content-Type"
+                            updateRes $ deleteHeader "Etag"
+                            updateRes $ deleteHeader "Last-Modified"
+
+               conn ← readCIHeader "Connection"
+               case conn of
+                 Nothing    → return ()
+                 Just value → when (value ≡ "close")
+                                  $ writeTVar itrWillClose True
+
+               willClose ← readTVar itrWillClose
                when willClose
-                        $ updateRes itr $ setHeader "Connection" "close"
+                   $ updateRes $ setHeader "Connection" "close"
 
-               when (reqMethod req == HEAD || not canHaveBody)
-                        $ writeTVar (itrWillDiscardBody itr) True
+               when (reqMethod ≡ HEAD ∨ not canHaveBody)
+                   $ writeTVar itrWillDiscardBody True
 
-      readHeader :: Interaction -> String -> STM (Maybe String)
-      readHeader itr name
-          = do valueMM <- readItrF itr itrResponse $ getHeader name
-               case valueMM of
-                 Just (Just val) -> return $ Just val
-                 _               -> return Nothing
+      readHeader ∷ CIAscii → STM (Maybe Ascii)
+      {-# INLINE readHeader #-}
+      readHeader k = getHeader k <$> readTVar itrResponse
 
-      updateRes :: Interaction -> (Response -> Response) -> STM ()
-      updateRes itr updator 
-          = updateItrF itr itrResponse updator
+      readCIHeader ∷ CIAscii → STM (Maybe CIAscii)
+      {-# INLINE readCIHeader #-}
+      readCIHeader k = getCIHeader k <$> readTVar itrResponse
 
+      updateRes ∷ (Response → Response) → STM ()
+      {-# INLINE updateRes #-}
+      updateRes f
+          = do old ← readTVar itrResponse
+               writeTVar itrResponse (f old)
 
-completeUnconditionalHeaders :: Config -> Response -> IO Response
-completeUnconditionalHeaders conf res
-    = return res >>= compServer >>= compDate >>= return
+completeUnconditionalHeaders ∷ Config → Response → IO Response
+completeUnconditionalHeaders conf = (compDate =≪) ∘ compServer
       where
-        compServer res
-            = case getHeader "Server" res of
-                Nothing -> return $ addHeader "Server" (cnfServerSoftware conf) res
-                Just _  -> return res
-
-        compDate res
-            = case getHeader "Date" res of
-                Nothing -> do time <- getClockTime
-                              return $ addHeader "Date" (formatHTTPDateTime time) res
-                Just _  -> return res
\ No newline at end of file
+        compServer res'
+            = case getHeader "Server" res' of
+                Nothing → return $ setHeader "Server" (cnfServerSoftware conf) res'
+                Just _  → return res'
+
+        compDate res'
+            = case getHeader "Date" res' of
+                Nothing → do date ← getCurrentDate
+                             return $ setHeader "Date" date res'
+                Just _  → return res'
+
+getCurrentDate ∷ IO Ascii
+getCurrentDate = HTTP.toAscii <$> getCurrentTime