]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Resource.hs
Added new actions to the Resource.
[Lucu.git] / Network / HTTP / Lucu / Resource.hs
index 7c1ceb0f027ee03d7aacbdb565cb81b16944a237..fcf23593e9ee89ca83d8c3e768242740c79ed717 100644 (file)
@@ -69,14 +69,18 @@ module Network.HTTP.Lucu.Resource
     -- |These actions can be computed regardless of the current state,
     -- and they don't change the state.
     , getConfig
+    , getRemoteAddr
+    , getRemoteAddr'
     , getRequest
     , getMethod
     , getRequestURI
+    , getRequestVersion
     , getResourcePath
     , getPathInfo
     , getQueryForm
     , getHeader
     , getAccept
+    , getAcceptEncoding
     , getContentType
 
     -- ** Finding an entity
@@ -109,6 +113,7 @@ module Network.HTTP.Lucu.Resource
     , redirect
     , setContentType
     , setLocation
+    , setContentEncoding
 
     -- ** Writing a response body
 
@@ -125,11 +130,12 @@ module Network.HTTP.Lucu.Resource
 
 import           Control.Concurrent.STM
 import           Control.Monad.Reader
+import           Data.Bits
 import qualified Data.ByteString.Lazy.Char8 as B
 import           Data.ByteString.Lazy.Char8 (ByteString)
+import           Data.Char
 import           Data.List
 import           Data.Maybe
-import           GHC.Conc (unsafeIOToSTM)
 import           Network.HTTP.Lucu.Abortion
 import           Network.HTTP.Lucu.Config
 import           Network.HTTP.Lucu.DefaultPage
@@ -138,12 +144,14 @@ import qualified Network.HTTP.Lucu.Headers as H
 import           Network.HTTP.Lucu.HttpVersion
 import           Network.HTTP.Lucu.Interaction
 import           Network.HTTP.Lucu.Parser
+import           Network.HTTP.Lucu.Parser.Http
 import           Network.HTTP.Lucu.Postprocess
 import           Network.HTTP.Lucu.RFC1123DateTime
 import           Network.HTTP.Lucu.Request
 import           Network.HTTP.Lucu.Response
 import           Network.HTTP.Lucu.MIMEType
 import           Network.HTTP.Lucu.Utils
+import           Network.Socket
 import           Network.URI
 import           System.Time
 
@@ -156,24 +164,54 @@ type Resource a = ReaderT Interaction IO a
 -- the httpd.
 getConfig :: Resource Config
 getConfig = do itr <- ask
-               return $ itrConfig itr
+               return $! itrConfig itr
+
+
+-- |Get the SockAddr of the remote host. If you want a string
+-- representation instead of SockAddr, use 'getRemoteAddr''.
+getRemoteAddr :: Resource SockAddr
+getRemoteAddr = do itr <- ask
+                   return $! itrRemoteAddr itr
+
+
+-- |Get the string representation of the address of remote host. If
+-- you want a SockAddr instead of String, use 'getRemoteAddr'.
+getRemoteAddr' :: Resource String
+getRemoteAddr' = do addr <- getRemoteAddr
+                    case addr of
+                      -- Network.Socket は IPv6 を考慮してゐないやうだ…
+                      (SockAddrInet _ v4addr)
+                          -> let b1 = (v4addr `shiftR` 24) .&. 0xFF
+                                 b2 = (v4addr `shiftR` 16) .&. 0xFF
+                                 b3 = (v4addr `shiftR`  8) .&. 0xFF
+                                 b4 =  v4addr              .&. 0xFF
+                             in
+                               return $ concat $ intersperse "." $ map show [b1, b2, b3, b4]
+                      (SockAddrUnix path)
+                          -> return path
+
 
 -- |Get the 'Network.HTTP.Lucu.Request.Request' value which represents
 -- the request header. In general you don't have to use this action.
 getRequest :: Resource Request
 getRequest = do itr <- ask
-                req <- liftIO $ atomically $ readItr itr itrRequest fromJust
+                req <- liftIO $! atomically $! readItr itr itrRequest fromJust
                 return req
 
 -- |Get the 'Network.HTTP.Lucu.Request.Method' value of the request.
 getMethod :: Resource Method
 getMethod = do req <- getRequest
-               return $ reqMethod req
+               return $! reqMethod req
 
 -- |Get the URI of the request.
 getRequestURI :: Resource URI
 getRequestURI = do req <- getRequest
-                   return $ reqURI req
+                   return $! reqURI req
+
+-- |Get the HTTP version of the request.
+getRequestVersion :: Resource HttpVersion
+getRequestVersion = do req <- getRequest
+                       return $! reqVersion req
 
 -- |Get the path of this 'Resource' (to be exact,
 -- 'Network.HTTP.Lucu.Resource.Tree.ResourceDef') in the
@@ -199,7 +237,7 @@ getRequestURI = do req <- getRequest
 -- >   }
 getResourcePath :: Resource [String]
 getResourcePath = do itr <- ask
-                     return $ fromJust $ itrResourcePath itr
+                     return $! fromJust $! itrResourcePath itr
 
 
 -- |This is an analogy of CGI PATH_INFO. Its result is always @[]@ if
@@ -215,45 +253,92 @@ getPathInfo = do rsrcPath <- getResourcePath
                  -- る。rsrcPath は全部一致してゐるに決まってゐる(でな
                  -- ければこの Resource が撰ばれた筈が無い)ので、
                  -- rsrcPath の長さの分だけ削除すれば良い。
-                 return $ drop (length rsrcPath) reqPath
+                 return $! drop (length rsrcPath) reqPath
 
 -- | Assume the query part of request URI as
 -- application\/x-www-form-urlencoded, and parse it. This action
 -- doesn't parse the request body. See 'inputForm'.
 getQueryForm :: Resource [(String, String)]
 getQueryForm = do reqURI <- getRequestURI
-                  return $ parseWWWFormURLEncoded $ uriQuery reqURI
+                  return $! parseWWWFormURLEncoded $ uriQuery reqURI
 
 -- |Get a value of given request header. Comparison of header name is
 -- case-insensitive. Note that this action is not intended to be used
 -- so frequently: there should be actions like 'getContentType' for
 -- every common headers.
 getHeader :: String -> Resource (Maybe String)
-getHeader name = do req <- getRequest
-                    return $ H.getHeader name req
+getHeader name = name `seq`
+                 do req <- getRequest
+                    return $! H.getHeader name req
 
 -- |Get a list of 'Network.HTTP.Lucu.MIMEType.MIMEType' enumerated on
 -- header \"Accept\".
 getAccept :: Resource [MIMEType]
-getAccept = do accept <- getHeader "Accept"
-               if accept == Nothing then
-                   return []
-                 else
-                   case parseStr mimeTypeListP $ fromJust accept of
-                     (Success xs, _) -> return xs
-                     _               -> return []
+getAccept = do acceptM <- getHeader "Accept"
+               case acceptM of
+                 Nothing 
+                     -> return []
+                 Just accept
+                     -> case parseStr mimeTypeListP accept of
+                          (Success xs, _) -> return xs
+                          _               -> abort BadRequest []
+                                             (Just $ "Unparsable Accept: " ++ accept)
+
+-- |Get a list of @(contentCoding, qvalue)@ enumerated on header
+-- \"Accept-Encoding\".
+getAcceptEncoding :: Resource [(String, Maybe Double)]
+getAcceptEncoding
+    = do accEncM <- getHeader "Accept-Encoding"
+         case accEncM of
+           Nothing
+               -- HTTP/1.0 には Accept-Encoding が無い場合の規定が無い
+               -- ので安全の爲 identity が指定された事にする。HTTP/1.1
+               -- の場合は何でも受け入れて良い事になってゐるので "*" が
+               -- 指定された事にする。
+               -> do ver <- getRequestVersion
+                     case ver of
+                       HttpVersion 1 0 -> return [("identity", Nothing)]
+                       HttpVersion 1 1 -> return [("*"       , Nothing)]
+           Just ""
+               -- identity のみが許される。
+               -> return [("identity", Nothing)]
+           Just accEnc
+               -> case parseStr accEncListP accEnc of
+                    (Success x, _) -> return x
+                    _              -> abort BadRequest []
+                                      (Just $ "Unparsable Accept-Encoding: " ++ accEnc)
+    where
+      accEncListP :: Parser [(String, Maybe Double)]
+      accEncListP = allowEOF $! listOf accEncP
+      
+      accEncP :: Parser (String, Maybe Double)
+      accEncP = do coding <- token
+                   qVal   <- option Nothing
+                             $ do string ";q="
+                                  q <- qvalue
+                                  return $ Just q
+                   return (normalizeCoding coding, qVal)
+
+      normalizeCoding :: String -> String
+      normalizeCoding coding
+          = case map toLower coding of
+              "x-gzip"     -> "gzip"
+              "x-compress" -> "compress"
+              other        -> other
 
 -- |Get the header \"Content-Type\" as
 -- 'Network.HTTP.Lucu.MIMEType.MIMEType'.
 getContentType :: Resource (Maybe MIMEType)
-getContentType = do cType <- getHeader "Content-Type"
-                    if cType == Nothing then
-                        return Nothing
-                      else
-                        case parseStr mimeTypeP $ fromJust cType of
-                          (Success t, _) -> return $ Just t
-                          _              -> return Nothing
-
+getContentType
+    = do cTypeM <- getHeader "Content-Type"
+         case cTypeM of
+           Nothing
+               -> return Nothing
+           Just cType
+               -> case parseStr mimeTypeP cType of
+                    (Success t, _) -> return $ Just t
+                    _              -> abort BadRequest []
+                                      (Just $ "Unparsable Content-Type: " ++ cType)
 
 
 {- ExaminingRequest 時に使用するアクション群 -}
@@ -274,11 +359,12 @@ getContentType = do cType <- getHeader "Content-Type"
 -- \"ETag\" and \"Last-Modified\" headers into the response.
 foundEntity :: ETag -> ClockTime -> Resource ()
 foundEntity tag timeStamp
-    = do driftTo ExaminingRequest
+    = tag `seq` timeStamp `seq`
+      do driftTo ExaminingRequest
 
          method <- getMethod
          when (method == GET || method == HEAD)
-                  $ setHeader' "Last-Modified" $ formatHTTPDateTime timeStamp
+                  $ setHeader' "Last-Modified" $! formatHTTPDateTime timeStamp
          when (method == POST)
                   $ abort InternalServerError []
                         (Just "Illegal computation of foundEntity for POST request.")
@@ -295,11 +381,12 @@ foundEntity tag timeStamp
 -- possible.
 foundETag :: ETag -> Resource ()
 foundETag tag
-    = do driftTo ExaminingRequest
+    = tag `seq`
+      do driftTo ExaminingRequest
       
          method <- getMethod
          when (method == GET || method == HEAD)
-                  $ setHeader' "ETag" $ show tag
+                  $ setHeader' "ETag" $! show tag
          when (method == POST)
                   $ abort InternalServerError []
                         (Just "Illegal computation of foundETag for POST request.")
@@ -315,8 +402,8 @@ foundETag tag
                               -- PreconditionFailed で終了。
                               -> when (not $ any (== tag) tags)
                                  $ abort PreconditionFailed []
-                                       $ Just ("The entity tag doesn't match: " ++ list)
-                          _   -> abort BadRequest [] $ Just ("Unparsable If-Match: " ++ fromJust ifMatch)
+                                       $! Just ("The entity tag doesn't match: " ++ list)
+                          _   -> abort BadRequest [] $! Just ("Unparsable If-Match: " ++ fromJust ifMatch)
 
          let statusForNoneMatch = if method == GET || method == HEAD then
                                       NotModified
@@ -327,12 +414,12 @@ foundETag tag
          ifNoneMatch <- getHeader "If-None-Match"
          case ifNoneMatch of
            Nothing   -> return ()
-           Just "*"  -> abort statusForNoneMatch [] $ Just ("The entity tag matches: *")
+           Just "*"  -> abort statusForNoneMatch [] $! Just ("The entity tag matches: *")
            Just list -> case parseStr eTagListP list of
                           (Success tags, _)
                               -> when (any (== tag) tags)
-                                 $ abort statusForNoneMatch [] $ Just ("The entity tag matches: " ++ list)
-                          _   -> abort BadRequest [] $ Just ("Unparsable If-None-Match: " ++ list)
+                                 $ abort statusForNoneMatch [] $! Just ("The entity tag matches: " ++ list)
+                          _   -> abort BadRequest [] $! Just ("Unparsable If-None-Match: " ++ list)
 
          driftTo GettingBody
 
@@ -348,11 +435,12 @@ foundETag tag
 -- possible.
 foundTimeStamp :: ClockTime -> Resource ()
 foundTimeStamp timeStamp
-    = do driftTo ExaminingRequest
+    = timeStamp `seq`
+      do driftTo ExaminingRequest
 
          method <- getMethod
          when (method == GET || method == HEAD)
-                  $ setHeader' "Last-Modified" $ formatHTTPDateTime timeStamp
+                  $ setHeader' "Last-Modified" $! formatHTTPDateTime timeStamp
          when (method == POST)
                   $ abort InternalServerError []
                         (Just "Illegal computation of foundTimeStamp for POST request.")
@@ -369,7 +457,7 @@ foundTimeStamp timeStamp
                          Just lastTime
                              -> when (timeStamp <= lastTime)
                                 $ abort statusForIfModSince []
-                                      $ Just ("The entity has not been modified since " ++ str)
+                                      $! Just ("The entity has not been modified since " ++ str)
                          Nothing
                              -> return () -- 不正な時刻は無視
            Nothing  -> return ()
@@ -381,7 +469,7 @@ foundTimeStamp timeStamp
                          Just lastTime
                              -> when (timeStamp > lastTime)
                                 $ abort PreconditionFailed []
-                                      $ Just  ("The entity has not been modified since " ++ str)
+                                      $! Just  ("The entity has not been modified since " ++ str)
                          Nothing
                              -> return () -- 不正な時刻は無視
            Nothing  -> return ()
@@ -398,7 +486,8 @@ foundTimeStamp timeStamp
 -- 'foundNoEntity' always aborts with status \"404 Not Found\".
 foundNoEntity :: Maybe String -> Resource ()
 foundNoEntity msgM
-    = do driftTo ExaminingRequest
+    = msgM `seq`
+      do driftTo ExaminingRequest
 
          method <- getMethod
          when (method /= PUT)
@@ -430,7 +519,8 @@ foundNoEntity msgM
 -- Note that 'inputBS' is more efficient than 'input' so you should
 -- use it whenever possible.
 input :: Int -> Resource String
-input limit = inputBS limit >>= return . B.unpack
+input limit = limit `seq`
+              inputBS limit >>= return . B.unpack
 
 
 -- | This is mostly the same as 'input' but is more
@@ -440,9 +530,10 @@ input limit = inputBS limit >>= return . B.unpack
 -- goes for 'inputChunkBS'.
 inputBS :: Int -> Resource ByteString
 inputBS limit
-    = do driftTo GettingBody
+    = limit `seq`
+      do driftTo GettingBody
          itr     <- ask
-         hasBody <- liftIO $ atomically $ readItr itr itrRequestHasBody id
+         hasBody <- liftIO $! atomically $! readItr itr itrRequestHasBody id
          chunk   <- if hasBody then
                         askForInput itr
                     else
@@ -452,7 +543,8 @@ inputBS limit
     where
       askForInput :: Interaction -> Resource ByteString
       askForInput itr
-          = do let defaultLimit = cnfMaxEntityLength $ itrConfig itr
+          = itr `seq`
+            do let defaultLimit = cnfMaxEntityLength $ itrConfig itr
                    actualLimit  = if limit <= 0 then
                                       defaultLimit
                                   else
@@ -460,40 +552,41 @@ inputBS limit
                when (actualLimit <= 0)
                         $ fail ("inputBS: limit must be positive: " ++ show actualLimit)
                -- Reader にリクエスト
-               liftIO $ atomically
-                          $ do chunkLen <- readItr itr itrReqChunkLength id
-                               writeItr itr itrWillReceiveBody True
-                               if fmap (> actualLimit) chunkLen == Just True then
-                                   -- 受信前から多過ぎる事が分かってゐる
-                                   tooLarge actualLimit
-                                 else
-                                   writeItr itr itrReqBodyWanted $ Just actualLimit
+               liftIO $! atomically
+                          $! do chunkLen <- readItr itr itrReqChunkLength id
+                                writeItr itr itrWillReceiveBody True
+                                if fmap (> actualLimit) chunkLen == Just True then
+                                    -- 受信前から多過ぎる事が分かってゐる
+                                    tooLarge actualLimit
+                                  else
+                                    writeItr itr itrReqBodyWanted $ Just actualLimit
                -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
-               chunk <- liftIO $ atomically
-                        $ do chunk       <- readItr itr itrReceivedBody id
-                             chunkIsOver <- readItr itr itrReqChunkIsOver id
-                             if B.length chunk < fromIntegral actualLimit then
-                                 -- 要求された量に滿たなくて、まだ殘り
-                                 -- があるなら再試行。
-                                 unless chunkIsOver
-                                            $ retry
-                               else
-                                 -- 制限値一杯まで讀むやうに指示したの
-                                 -- にまだ殘ってゐるなら、それは多過ぎ
-                                 -- る。
-                                 unless chunkIsOver
-                                            $ tooLarge actualLimit
-                             -- 成功。itr 内にチャンクを置いたままにす
-                             -- るとメモリの無駄になるので除去。
-                             writeItr itr itrReceivedBody B.empty
-                             return chunk
+               chunk <- liftIO $! atomically
+                        $! do chunk       <- readItr itr itrReceivedBody id
+                              chunkIsOver <- readItr itr itrReqChunkIsOver id
+                              if B.length chunk < fromIntegral actualLimit then
+                                  -- 要求された量に滿たなくて、まだ殘り
+                                  -- があるなら再試行。
+                                  unless chunkIsOver
+                                             $ retry
+                                else
+                                  -- 制限値一杯まで讀むやうに指示したの
+                                  -- にまだ殘ってゐるなら、それは多過ぎ
+                                  -- る。
+                                  unless chunkIsOver
+                                             $ tooLarge actualLimit
+                              -- 成功。itr 内にチャンクを置いたままにす
+                              -- るとメモリの無駄になるので除去。
+                              writeItr itr itrReceivedBody B.empty
+                              return chunk
                driftTo DecidingHeader
                return chunk
 
       tooLarge :: Int -> STM ()
-      tooLarge lim = abortSTM RequestEntityTooLarge []
-                     $ Just ("Request body must be smaller than "
-                             ++ show lim ++ " bytes.")
+      tooLarge lim = lim `seq`
+                     abortSTM RequestEntityTooLarge []
+                     $! Just ("Request body must be smaller than "
+                              ++ show lim ++ " bytes.")
          
 -- | Computation of @'inputChunk' limit@ attempts to read a part of
 -- request body up to @limit@ bytes. You can read any large request by
@@ -509,14 +602,16 @@ inputBS limit
 -- Note that 'inputChunkBS' is more efficient than 'inputChunk' so you
 -- should use it whenever possible.
 inputChunk :: Int -> Resource String
-inputChunk limit = inputChunkBS limit >>= return . B.unpack
+inputChunk limit = limit `seq`
+                   inputChunkBS limit >>= return . B.unpack
 
 
 -- | This is mostly the same as 'inputChunk' but is more
 -- efficient. See 'inputBS'.
 inputChunkBS :: Int -> Resource ByteString
 inputChunkBS limit
-    = do driftTo GettingBody
+    = limit `seq`
+      do driftTo GettingBody
          itr <- ask
          hasBody <- liftIO $ atomically $ readItr itr itrRequestHasBody id
          chunk   <- if hasBody then
@@ -528,7 +623,8 @@ inputChunkBS limit
     where
       askForInput :: Interaction -> Resource ByteString
       askForInput itr
-          = do let defaultLimit = cnfMaxEntityLength $ itrConfig itr
+          = itr `seq`
+            do let defaultLimit = cnfMaxEntityLength $! itrConfig itr
                    actualLimit  = if limit < 0 then
                                       defaultLimit
                                   else
@@ -536,11 +632,11 @@ inputChunkBS limit
                when (actualLimit <= 0)
                         $ fail ("inputChunkBS: limit must be positive: " ++ show actualLimit)
                -- Reader にリクエスト
-               liftIO $ atomically
-                          $ do writeItr itr itrReqBodyWanted $ Just actualLimit
-                               writeItr itr itrWillReceiveBody True
+               liftIO $! atomically
+                          $! do writeItr itr itrReqBodyWanted $! Just actualLimit
+                                writeItr itr itrWillReceiveBody True
                -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
-               chunk <- liftIO $ atomically
+               chunk <- liftIO $! atomically
                         $ do chunk <- readItr itr itrReceivedBody id
                              -- 要求された量に滿たなくて、まだ殘りがあ
                              -- るなら再試行。
@@ -567,7 +663,8 @@ inputChunkBS limit
 -- it is not (yet) done.
 inputForm :: Int -> Resource [(String, String)]
 inputForm limit
-    = do cTypeM <- getContentType
+    = limit `seq` 
+      do cTypeM <- getContentType
          case cTypeM of
            Nothing
                -> abort BadRequest [] (Just "Missing Content-Type")
@@ -576,7 +673,7 @@ inputForm limit
            Just (MIMEType "multipart" "form-data" _)
                -> readMultipartFormData
            Just cType
-               -> abort UnsupportedMediaType [] (Just $ "Unsupported media type: "
+               -> abort UnsupportedMediaType [] (Just $! "Unsupported media type: "
                                                           ++ show cType)
     where
       readWWWFormURLEncoded
@@ -585,7 +682,7 @@ inputForm limit
 
       readMultipartFormData -- FIXME: 未對應
           = abort UnsupportedMediaType []
-            (Just $ "Sorry, inputForm does not currently support multipart/form-data.")
+            (Just $! "Sorry, inputForm does not currently support multipart/form-data.")
 
 -- | This is just a constant -1. It's better to say @'input'
 -- 'defaultLimit'@ than to say @'input' (-1)@ but these are exactly
@@ -601,12 +698,13 @@ defaultLimit = (-1)
 -- the status code will be defaulted to \"200 OK\".
 setStatus :: StatusCode -> Resource ()
 setStatus code
-    = do driftTo DecidingHeader
+    = code `seq`
+      do driftTo DecidingHeader
          itr <- ask
-         liftIO $ atomically $ updateItr itr itrResponse
-                    $ \ res -> res {
-                                 resStatus = code
-                               }
+         liftIO $! atomically $! updateItr itr itrResponse
+                    $! \ res -> res {
+                                  resStatus = code
+                                }
 
 -- | Set a value of given resource header. Comparison of header name
 -- is case-insensitive. Note that this action is not intended to be
@@ -624,12 +722,14 @@ setStatus code
 -- a part of header of the next response.
 setHeader :: String -> String -> Resource ()
 setHeader name value
-    = driftTo DecidingHeader >> setHeader' name value
+    = name `seq` value `seq`
+      driftTo DecidingHeader >> setHeader' name value
          
 
-setHeader' :: String -> String -> Resource()
+setHeader' :: String -> String -> Resource ()
 setHeader' name value
-    = do itr <- ask
+    = name `seq` value `seq`
+      do itr <- ask
          liftIO $ atomically
                     $ updateItr itr itrResponse
                           $ H.setHeader name value
@@ -639,17 +739,20 @@ setHeader' name value
 -- 'Network.HTTP.Lucu.Response.isRedirection' or it causes an error.
 redirect :: StatusCode -> URI -> Resource ()
 redirect code uri
-    = do when (code == NotModified || not (isRedirection code))
+    = code `seq` uri `seq`
+      do when (code == NotModified || not (isRedirection code))
                   $ abort InternalServerError []
-                        $ Just ("Attempted to redirect with status " ++ show code)
+                        $! Just ("Attempted to redirect with status " ++ show code)
          setStatus code
          setLocation uri
+{-# INLINE redirect #-}
+
 
 -- | Computation of @'setContentType' mType@ sets the response header
 -- \"Content-Type\" to @mType@.
 setContentType :: MIMEType -> Resource ()
 setContentType mType
-    = setHeader "Content-Type" $ show mType
+    = setHeader "Content-Type" $! show mType
 
 -- | Computation of @'setLocation' uri@ sets the response header
 -- \"Location\" to @uri@.
@@ -657,6 +760,12 @@ setLocation :: URI -> Resource ()
 setLocation uri
     = setHeader "Location" $ uriToString id uri $ ""
 
+-- |Computation of @'setContentEncoding' codings@ sets the response
+-- header \"Content-Encoding\" to @codings@.
+setContentEncoding :: [String] -> Resource ()
+setContentEncoding codings
+    = setHeader "Content-Encoding" $ joinWith ", " codings
+
 
 {- DecidingBody 時に使用するアクション群 -}
 
@@ -668,12 +777,14 @@ setLocation uri
 -- Note that 'outputBS' is more efficient than 'output' so you should
 -- use it whenever possible.
 output :: String -> Resource ()
-output = outputBS . B.pack
+output str = outputBS $! B.pack str
+{-# INLINE output #-}
 
 -- | This is mostly the same as 'output' but is more efficient.
 outputBS :: ByteString -> Resource ()
 outputBS str = do outputChunkBS str
                   driftTo Done
+{-# INLINE outputBS #-}
 
 -- | Computation of @'outputChunk' str@ writes @str@ as a part of
 -- response body. You can compute this action multiple times to write
@@ -683,12 +794,14 @@ outputBS str = do outputChunkBS str
 -- Note that 'outputChunkBS' is more efficient than 'outputChunk' so
 -- you should use it whenever possible.
 outputChunk :: String -> Resource ()
-outputChunk = outputChunkBS . B.pack
+outputChunk str = outputChunkBS $! B.pack str
+{-# INLINE outputChunk #-}
 
 -- | This is mostly the same as 'outputChunk' but is more efficient.
 outputChunkBS :: ByteString -> Resource ()
 outputChunkBS str
-    = do driftTo DecidingBody
+    = str `seq`
+      do driftTo DecidingBody
          itr <- ask
          
          let limit = cnfMaxOutputChunkLength $ itrConfig itr
@@ -749,7 +862,8 @@ outputChunkBS str
 
 driftTo :: InteractionState -> Resource ()
 driftTo newState
-    = do itr <- ask
+    = newState `seq`
+      do itr <- ask
          liftIO $ atomically $ do oldState <- readItr itr itrState id
                                   if newState < oldState then
                                       throwStateError oldState newState