]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Resource.hs
The library now compiles, and I'm now working on ImplantFile.hs
[Lucu.git] / Network / HTTP / Lucu / Resource.hs
index 2672399bf7a249102d2368d387bc529dcfdae017..01b61813971e9e1ce4ba80e18ed374e400a5ce5a 100644 (file)
@@ -1,12 +1,10 @@
 {-# LANGUAGE
-    BangPatterns
-  , GeneralizedNewtypeDeriving
+    GeneralizedNewtypeDeriving
   , DoAndIfThenElse
   , OverloadedStrings
   , RecordWildCards
   , UnicodeSyntax
   #-}
-{-# OPTIONS_HADDOCK prune #-}
 
 -- |This is the Resource Monad; monadic actions to define the behavior
 -- of each resources. The 'Resource' Monad is a kind of 'Prelude.IO'
@@ -71,7 +69,7 @@ module Network.HTTP.Lucu.Resource
     -- * Types
       Resource
     , FormData(..)
-    , runRes -- private
+    , runRes
 
     -- * Actions
 
@@ -139,6 +137,8 @@ module Network.HTTP.Lucu.Resource
     , driftTo -- private
     )
     where
+import Blaze.ByteString.Builder (Builder)
+import qualified Blaze.ByteString.Builder.ByteString as BB
 import Control.Applicative
 import Control.Concurrent.STM
 import Control.Monad.Reader
@@ -148,18 +148,18 @@ import qualified Data.Ascii as A
 import qualified Data.Attoparsec.Char8 as P
 import qualified Data.Attoparsec.Lazy  as LP
 import Data.ByteString (ByteString)
-import qualified Data.ByteString.Char8 as C8
-import qualified Data.ByteString.Lazy  as Lazy
-import qualified Data.ByteString.Lazy.Char8 as L8
+import qualified Data.ByteString as Strict
+import qualified Data.ByteString.Lazy as Lazy
+import Data.Foldable (toList)
 import Data.List
 import qualified Data.Map as M
 import Data.Maybe
+import Data.Monoid
 import Data.Monoid.Unicode
-import qualified Data.Sequence as S
+import Data.Sequence (Seq)
 import Data.Text (Text)
 import qualified Data.Text as T
 import qualified Data.Text.Encoding as T
-import qualified Data.Text.Encoding.Error as T
 import Data.Time
 import qualified Data.Time.HTTP as HTTP
 import Network.HTTP.Lucu.Abortion
@@ -235,9 +235,7 @@ getRemoteCertificate = itrRemoteCert <$> getInteraction
 -- |Get the 'Request' value which represents the request header. In
 -- general you don't have to use this action.
 getRequest ∷ Resource Request
-getRequest
-    = do itr ← getInteraction
-         liftIO $ atomically $ readItr itrRequest fromJust itr
+getRequest = (fromJust ∘ itrRequest) <$> getInteraction
 
 -- |Get the 'Method' value of the request.
 getMethod ∷ Resource Method
@@ -273,24 +271,24 @@ getRequestVersion = reqVersion <$> getRequest
 -- >                        ...
 -- >   , ...
 -- >   }
-getResourcePath ∷ Resource [Ascii]
+getResourcePath ∷ Resource [Text]
 getResourcePath = (fromJust ∘ itrResourcePath) <$> getInteraction
 
 -- |This is an analogy of CGI PATH_INFO. The result is
 -- URI-unescaped. It is always @[]@ if the
 -- 'Network.HTTP.Lucu.Resource.Tree.ResourceDef' is not greedy. See
 -- 'getResourcePath'.
-getPathInfo ∷ Resource [ByteString]
+--
+-- Note that the returned path is URI-decoded and then UTF-8 decoded.
+getPathInfo ∷ Resource [Text]
 getPathInfo = do rsrcPath ← getResourcePath
-                 uri      ← getRequestURI
-                 let reqPathStr = uriPath uri
-                     reqPath    = [unEscapeString x | x ← splitBy (≡ '/') reqPathStr, (¬) (null x)]
+                 reqPath  ← splitPathInfo <$> getRequestURI
                  -- rsrcPath と reqPath の共通する先頭部分を reqPath か
                  -- ら全部取り除くと、それは PATH_INFO のやうなものにな
                  -- る。rsrcPath は全部一致してゐるに決まってゐる(でな
                  -- ければこの Resource が撰ばれた筈が無い)ので、
                  -- rsrcPath の長さの分だけ削除すれば良い。
-                 return $ map C8.pack $ 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 to pairs of
@@ -310,9 +308,9 @@ toPairWithFormData ∷ (ByteString, ByteString) → (Text, FormData)
 toPairWithFormData (name, value)
     = let fd = FormData {
                  fdFileName = Nothing
-               , fdContent  = L8.fromChunks [value]
+               , fdContent  = Lazy.fromChunks [value]
                }
-      in (T.decodeUtf8With T.lenientDecode name, fd)
+      in (T.decodeUtf8 name, fd)
 
 -- |Get a value of given request header. Comparison of header name is
 -- case-insensitive. Note that this action is not intended to be used
@@ -432,7 +430,7 @@ getAuthorization
 -- If this is a GET or HEAD request, 'foundEntity' automatically puts
 -- \"ETag\" and \"Last-Modified\" headers into the response.
 foundEntity ∷ ETag → UTCTime → Resource ()
-foundEntity !tag !timeStamp
+foundEntity tag timeStamp
     = do driftTo ExaminingRequest
 
          method ← getMethod
@@ -453,7 +451,7 @@ foundEntity !tag !timeStamp
 -- This action is not preferred. You should use 'foundEntity' whenever
 -- possible.
 foundETag ∷ ETag → Resource ()
-foundETag !tag
+foundETag tag
     = do driftTo ExaminingRequest
       
          method ← getMethod
@@ -607,17 +605,16 @@ input ∷ Int → Resource Lazy.ByteString
 input limit
     = do driftTo GettingBody
          itr     ← getInteraction
-         hasBody ← liftIO $ atomically $ readItr itrRequestHasBody id itr
-         chunk   ← if hasBody then
+         chunk   ← if reqHasBody $ fromJust $ itrRequest itr then
                        askForInput itr
                    else
                        do driftTo DecidingHeader
-                          return L8.empty
+                          return (∅)
          return chunk
     where
       askForInput ∷ Interaction → Resource Lazy.ByteString
-      askForInput itr
-          = do let confLimit   = cnfMaxEntityLength $ itrConfig itr
+      askForInput (Interaction {..})
+          = do let confLimit   = cnfMaxEntityLength itrConfig
                    actualLimit = if limit ≤ 0 then
                                      confLimit
                                  else
@@ -626,18 +623,12 @@ input limit
                         $ fail ("inputLBS: limit must be positive: " ⧺ show actualLimit)
                -- Reader にリクエスト
                liftIO $ atomically
-                      $ do chunkLen ← readItr itrReqChunkLength id itr
-                           writeItr itrWillReceiveBody True itr
-                           if fmap (> actualLimit) chunkLen ≡ Just True then
-                               -- 受信前から多過ぎる事が分かってゐる
-                               tooLarge actualLimit
-                           else
-                               writeItr itrReqBodyWanted (Just actualLimit) itr
+                      $ writeTVar itrReqBodyWanted actualLimit
                -- 應答を待つ。トランザクションを分けなければ當然デッドロックする。
                chunk ← liftIO $ atomically
-                       $ do chunk       ← readItr itrReceivedBody chunksToLBS itr
-                            chunkIsOver ← readItr itrReqChunkIsOver id itr
-                            if L8.length chunk < fromIntegral actualLimit then
+                       $ do chunkLen    ← readTVar itrReceivedBodyLen
+                            chunkIsOver ← readTVar itrReqChunkIsOver
+                            if chunkLen < actualLimit then
                                 -- 要求された量に滿たなくて、まだ殘りが
                                 -- あるなら再試行。
                                 unless chunkIsOver
@@ -649,8 +640,11 @@ input limit
                                     $ tooLarge actualLimit
                             -- 成功。itr 内にチャンクを置いたままにする
                             -- とメモリの無駄になるので除去。
-                            writeItr itrReceivedBody (∅) itr
+                            chunk ← seqToLBS <$> readTVar itrReceivedBody
+                            writeTVar itrReceivedBody    (∅)
+                            writeTVar itrReceivedBodyLen 0
                             return chunk
+
                driftTo DecidingHeader
                return chunk
 
@@ -658,6 +652,10 @@ input limit
       tooLarge lim = abortSTM RequestEntityTooLarge []
                      (Just $ "Request body must be smaller than "
                              ⊕ T.pack (show lim) ⊕ " bytes.")
+
+seqToLBS ∷ Seq ByteString → Lazy.ByteString
+{-# INLINE seqToLBS #-}
+seqToLBS = Lazy.fromChunks ∘ toList
          
 -- | Computation of @'inputChunk' limit@ attempts to read a part of
 -- request body up to @limit@ bytes. You can read any large request by
@@ -675,50 +673,55 @@ inputChunk ∷ Int → Resource Lazy.ByteString
 inputChunk limit
     = do driftTo GettingBody
          itr     ← getInteraction
-         hasBody ← liftIO $ atomically $ readItr itrRequestHasBody id itr
-         chunk   ← if hasBody then
-                        askForInput itr
-                    else
-                        do driftTo DecidingHeader
-                           return L8.empty
+         chunk   ← if reqHasBody $ fromJust $ itrRequest itr then
+                       askForInput itr
+                   else
+                       do driftTo DecidingHeader
+                          return (∅)
          return chunk
     where
       askForInput ∷ Interaction → Resource Lazy.ByteString
-      askForInput itr
-          = do let confLimit   = cnfMaxEntityLength $ itrConfig itr
+      askForInput (Interaction {..})
+          = do let confLimit   = cnfMaxEntityLength itrConfig
                    actualLimit = if limit < 0 then
-                                      confLimit
-                                  else
-                                      limit
-               when (actualLimit <= 0)
+                                     confLimit
+                                 else
+                                     limit
+               when (actualLimit  0)
                         $ fail ("inputChunkLBS: limit must be positive: " ++ show actualLimit)
                -- Reader にリクエスト
                liftIO $ atomically
-                          $ do writeItr itrReqBodyWanted (Just actualLimit) itr
-                               writeItr itrWillReceiveBody True itr
+                      $ writeTVar itrReqBodyWanted actualLimit
                -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
                chunk ← liftIO $ atomically
-                        $ do chunk ← readItr itrReceivedBody chunksToLBS itr
-                             -- 要求された量に滿たなくて、まだ殘りがあ
-                             -- るなら再試行。
-                             when (L8.length chunk < fromIntegral actualLimit)
-                                      $ do chunkIsOver ← readItr itrReqChunkIsOver id itr
-                                           unless chunkIsOver
-                                               $ retry
-                             -- 成功
-                             writeItr itrReceivedBody (∅) itr
-                             return chunk
-               when (L8.null chunk)
+                       $ do chunkLen ← readTVar itrReceivedBodyLen
+                            -- 要求された量に滿たなくて、まだ殘りがある
+                            -- なら再試行。
+                            when (chunkLen < actualLimit)
+                                $ do chunkIsOver ← readTVar itrReqChunkIsOver
+                                     unless chunkIsOver
+                                         $ retry
+                            -- 成功
+                            chunk ← seqToLBS <$> readTVar itrReceivedBody
+                            writeTVar itrReceivedBody    (∅)
+                            writeTVar itrReceivedBodyLen 0
+                            return chunk
+               when (Lazy.null chunk)
                    $ driftTo DecidingHeader
                return chunk
 
 -- | Computation of @'inputForm' limit@ attempts to read the request
 -- body with 'input' and parse it as
--- application\/x-www-form-urlencoded or multipart\/form-data. If the
--- request header \"Content-Type\" is neither of them, 'inputForm'
+-- @application\/x-www-form-urlencoded@ or @multipart\/form-data@. If
+-- the request header \"Content-Type\" is neither of them, 'inputForm'
 -- makes 'Resource' abort with status \"415 Unsupported Media
 -- Type\". If the request has no \"Content-Type\", it aborts with
 -- \"400 Bad Request\".
+--
+-- Field names in @multipart\/form-data@ will be precisely decoded in
+-- accordance with RFC 2231. On the other hand,
+-- @application\/x-www-form-urlencoded@ says nothing about the
+-- encoding of field names, so they'll always be decoded in UTF-8.
 inputForm ∷ Int → Resource [(Text, FormData)]
 inputForm limit
     = do cTypeM ← getContentType
@@ -731,7 +734,11 @@ inputForm limit
                → readMultipartFormData params
            Just cType
                → abort UnsupportedMediaType []
-                 (Just $ "Unsupported media type: " ⊕ A.toText (printMIMEType cType))
+                 $ Just
+                 $ A.toText
+                 $ A.fromAsciiBuilder
+                 $ A.toAsciiBuilder "Unsupported media type: "
+                 ⊕ printMIMEType cType
     where
       readWWWFormURLEncoded
           = (map toPairWithFormData ∘ parseWWWFormURLEncoded)
@@ -739,7 +746,7 @@ inputForm limit
             (bsToAscii =≪ input limit)
 
       bsToAscii bs
-          = case A.fromByteString (C8.concat (L8.toChunks bs)) of
+          = case A.fromByteString (Strict.concat (Lazy.toChunks bs)) of
               Just a  → return a
               Nothing → abort BadRequest [] (Just "Malformed x-www-form-urlencoded")
 
@@ -774,14 +781,12 @@ defaultLimit = (-1)
 -- | Set the response status code. If you omit to compute this action,
 -- the status code will be defaulted to \"200 OK\".
 setStatus ∷ StatusCode → Resource ()
-setStatus code
+setStatus sc
     = do driftTo DecidingHeader
          itr ← getInteraction
-         liftIO $ atomically $ updateItr itrResponse f itr
-    where
-      f res = res {
-                resStatus = code
-              }
+         liftIO
+             $ atomically
+             $ setResponseStatus itr sc
 
 -- | Set a value of given resource header. Comparison of header name
 -- is case-insensitive. Note that this action is not intended to be
@@ -805,7 +810,9 @@ setHeader' ∷ CIAscii → Ascii → Resource ()
 setHeader' name value
     = do itr ← getInteraction
          liftIO $ atomically
-                $ updateItr itrResponse (H.setHeader name value) itr
+                $ do res ← readTVar $ itrResponse itr
+                     let res' = H.setHeader name value res
+                     writeTVar (itrResponse itr) res'
 
 -- | Computation of @'redirect' code uri@ sets the response status to
 -- @code@ and \"Location\" header to @uri@. The @code@ must satisfy
@@ -814,15 +821,19 @@ redirect ∷ StatusCode → URI → Resource ()
 redirect code uri
     = do when (code ≡ NotModified ∨ not (isRedirection code))
              $ abort InternalServerError []
-               (Just $ "Attempted to redirect with status " ⊕ A.toText (printStatusCode code))
+             $ Just
+             $ A.toText
+             $ A.fromAsciiBuilder
+             $ A.toAsciiBuilder "Attempted to redirect with status "
+             ⊕ printStatusCode code
          setStatus code
          setLocation uri
 
 -- | Computation of @'setContentType' mType@ sets the response header
 -- \"Content-Type\" to @mType@.
 setContentType ∷ MIMEType → Resource ()
-setContentType mType
-    = setHeader "Content-Type" (printMIMEType mType)
+setContentType
+    = setHeader "Content-Type" ∘ A.fromAsciiBuilder ∘ printMIMEType
 
 -- | Computation of @'setLocation' uri@ sets the response header
 -- \"Location\" to @uri@.
@@ -859,19 +870,16 @@ setWWWAuthenticate challenge
 
 {- DecidingBody 時に使用するアクション群 -}
 
--- | Computation of @'output' str@ writes @str@ as a response body,
--- and then make the 'Resource' transit to /Done/ state. It is safe to
--- apply 'output' to an infinite string, such as a lazy stream of
--- \/dev\/random.
+-- | Write a 'Lazy.ByteString' to the response body, and then transit
+-- to the /Done/ state. It is safe to apply 'output' to an infinite
+-- string, such as the lazy stream of \/dev\/random.
 output ∷ Lazy.ByteString → Resource ()
 {-# INLINE output #-}
-output str = do outputChunk str
-                driftTo Done
+output str = outputChunk str *> driftTo Done
 
--- | Computation of @'outputChunk' str@ writes @str@ as a part of
--- response body. You can compute this action multiple times to write
--- a body little at a time. It is safe to apply 'outputChunk' to an
--- infinite string.
+-- | Write a 'Lazy.ByteString' to the response body. This action can
+-- be repeated as many times as you want. It is safe to apply
+-- 'outputChunk' to an infinite string.
 outputChunk ∷ Lazy.ByteString → Resource ()
 outputChunk wholeChunk
     = do driftTo DecidingBody
@@ -882,36 +890,24 @@ outputChunk wholeChunk
              $ abort InternalServerError []
                (Just $ "cnfMaxOutputChunkLength must be positive: " ⊕ T.pack (show limit))
 
-         discardBody ← liftIO $ atomically $
-                       readItr itrWillDiscardBody id itr
-
+         discardBody ← liftIO $ atomically $ readTVar $ itrWillDiscardBody itr
          unless (discardBody)
-             $ sendChunks wholeChunk limit
+             $ sendChunks itr wholeChunk limit
 
-         unless (L8.null wholeChunk)
+         unless (Lazy.null wholeChunk)
              $ liftIO $ atomically $
-               writeItr itrBodyIsNull False itr
+               writeTVar (itrSentNoBodySoFar itr) False
     where
-      -- チャンクの大きさは Config で制限されてゐる。もし例へば
-      -- "/dev/zero" を L8.readFile して作った Lazy.ByteString をそのまま
-      -- ResponseWriter に渡したりすると大變な事が起こる。何故なら
-      -- ResponseWriter は Transfer-Encoding: chunked の時、ヘッダを書
-      -- く爲にチャンクの大きさを測るからだ。
-      sendChunks ∷ Lazy.ByteString → Int → Resource ()
-      sendChunks str limit
-          | L8.null str = return ()
-          | otherwise   = do let (chunk, remaining) = L8.splitAt (fromIntegral limit) str
-                             itr ← getInteraction
-                             liftIO $ atomically $ 
-                                 do buf ← readItr itrBodyToSend id itr
-                                    if S.null buf then
-                                        -- バッファが消化された
-                                        writeItr itrBodyToSend (chunksFromLBS chunk) itr
-                                    else
-                                        -- 消化されるのを待つ
-                                        retry
-                             -- 殘りのチャンクについて繰り返す
-                             sendChunks remaining limit
+      sendChunks ∷ Interaction → Lazy.ByteString → Int → Resource ()
+      sendChunks itr@(Interaction {..}) str limit
+          | Lazy.null str = return ()
+          | otherwise     = do let (chunk, remaining) = Lazy.splitAt (fromIntegral limit) str
+                               liftIO $ atomically
+                                      $ putTMVar itrBodyToSend (chunkToBuilder chunk)
+                               sendChunks itr remaining limit
+
+      chunkToBuilder ∷ Lazy.ByteString → Builder
+      chunkToBuilder = mconcat ∘ map BB.fromByteString ∘ Lazy.toChunks
 
 {-
 
@@ -935,37 +931,31 @@ outputChunk wholeChunk
 driftTo ∷ InteractionState → Resource ()
 driftTo newState
     = do itr ← getInteraction
-         liftIO $ atomically $ do oldState ← readItr itrState id itr
-                                  if newState < oldState then
-                                      throwStateError oldState newState
-                                    else
-                                      do let a = [oldState .. newState]
-                                             b = tail a
-                                             c = zip a b
-                                         mapM_ (uncurry $ drift itr) c
-                                         writeItr itrState newState itr
+         liftIO $ atomically
+                $ do oldState ← readTVar $ itrState itr
+                     if newState < oldState then
+                         throwStateError oldState newState
+                     else
+                         do let a = [oldState .. newState]
+                                b = tail a
+                                c = zip a b
+                            mapM_ (uncurry $ drift itr) c
+                            writeTVar (itrState itr) newState
     where
-      throwStateError ∷ Monad m => InteractionState → InteractionState → m a
-
+      throwStateError ∷ Monad m ⇒ InteractionState → InteractionState → m a
       throwStateError Done DecidingBody
           = fail "It makes no sense to output something after finishing to output."
-
       throwStateError old new
           = fail ("state error: " ⧺ show old ⧺ " ==> " ⧺ show new)
 
-
       drift ∷ Interaction → InteractionState → InteractionState → STM ()
-
-      drift itr GettingBody _
-          = writeItr itrReqBodyWasteAll True itr
-
+      drift (Interaction {..}) GettingBody _
+          = writeTVar itrReqBodyWasteAll True
       drift itr DecidingHeader _
           = postprocess itr
-
-      drift itr _ Done
-          = do bodyIsNull ← readItr itrBodyIsNull id itr
+      drift itr@(Interaction {..}) _ Done
+          = do bodyIsNull ← readTVar itrSentNoBodySoFar
                when bodyIsNull
-                        $ writeDefaultPage itr
-
+                   $ writeDefaultPage itr
       drift _ _ _
           = return ()