]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Resource.hs
examples/HelloWorld.hs fully works now.
[Lucu.git] / Network / HTTP / Lucu / Resource.hs
index 298b9b2541edd0f4d3d8b170bccb6cc9965bfe4e..c75421378c89dd1c5eb6b25b5fea31cf354ce5a5 100644 (file)
@@ -6,7 +6,6 @@
   , 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'
 -- Monad thus it implements 'Control.Monad.Trans.MonadIO' class. It is
@@ -70,7 +69,7 @@ module Network.HTTP.Lucu.Resource
     -- * Types
       Resource
     , FormData(..)
-    , runRes -- private
+    , runRes
 
     -- * Actions
 
@@ -212,7 +211,7 @@ getRemoteAddr = itrRemoteAddr <$> getInteraction
 getRemoteAddr' ∷ Resource HostName
 getRemoteAddr'
     = do sa          ← getRemoteAddr
-         (Just a, _) ← liftIO $ getNameInfo [NI_NUMERICHOST] False False sa
+         (Just a, _) ← liftIO $ getNameInfo [NI_NUMERICHOST] True False sa
          return a
 
 -- |Resolve an address to the remote host.
@@ -253,7 +252,7 @@ getRequestVersion = reqVersion <$> getRequest
 -- |Get the path of this 'Resource' (to be exact,
 -- 'Network.HTTP.Lucu.Resource.Tree.ResourceDef') in the
 -- 'Network.HTTP.Lucu.Resource.Tree.ResTree'. The result of this
--- action is the exact path in the tree even if the
+-- action is the exact path in the tree even when the
 -- 'Network.HTTP.Lucu.Resource.Tree.ResourceDef' is greedy.
 --
 -- Example:
@@ -263,9 +262,9 @@ getRequestVersion = reqVersion <$> getRequest
 -- >
 -- > resFoo = ResourceDef {
 -- >     resIsGreedy = True
--- >   , resGet = Just $ do requestURI    getRequestURI
--- >                        resourcePath  getResourcePath
--- >                        pathInfo      getPathInfo
+-- >   , resGet = Just $ do requestURI   <- getRequestURI
+-- >                        resourcePath <- getResourcePath
+-- >                        pathInfo     <- getPathInfo
 -- >                        -- uriPath requestURI == "/foo/bar/baz"
 -- >                        -- resourcePath       == ["foo"]
 -- >                        -- pathInfo           == ["bar", "baz"]
@@ -457,7 +456,9 @@ foundETag tag
       
          method ← getMethod
          when (method ≡ GET ∨ method ≡ HEAD)
-              $ setHeader' "ETag" (printETag tag)
+              $ setHeader' "ETag"
+              $ A.fromAsciiBuilder
+              $ printETag tag
          when (method ≡ POST)
               $ abort InternalServerError []
                 (Just "Illegal computation of foundETag for POST request.")
@@ -624,7 +625,7 @@ input limit
                         $ fail ("inputLBS: limit must be positive: " ⧺ show actualLimit)
                -- Reader にリクエスト
                liftIO $ atomically
-                      $ writeTVar itrReqBodyWanted (Just actualLimit)
+                      $ writeTVar itrReqBodyWanted actualLimit
                -- 應答を待つ。トランザクションを分けなければ當然デッドロックする。
                chunk ← liftIO $ atomically
                        $ do chunkLen    ← readTVar itrReceivedBodyLen
@@ -692,7 +693,7 @@ inputChunk limit
                         $ fail ("inputChunkLBS: limit must be positive: " ++ show actualLimit)
                -- Reader にリクエスト
                liftIO $ atomically
-                      $ writeTVar itrReqBodyWanted (Just actualLimit)
+                      $ writeTVar itrReqBodyWanted actualLimit
                -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
                chunk ← liftIO $ atomically
                        $ do chunkLen ← readTVar itrReceivedBodyLen
@@ -882,33 +883,13 @@ output str = outputChunk str *> driftTo Done
 -- be repeated as many times as you want. It is safe to apply
 -- 'outputChunk' to an infinite string.
 outputChunk ∷ Lazy.ByteString → Resource ()
-outputChunk wholeChunk
+outputChunk str
     = do driftTo DecidingBody
          itr ← getInteraction
-         
-         let limit = cnfMaxOutputChunkLength $ itrConfig itr
-         when (limit ≤ 0)
-             $ abort InternalServerError []
-               (Just $ "cnfMaxOutputChunkLength must be positive: " ⊕ T.pack (show limit))
-
-         discardBody ← liftIO $ atomically $ readTVar $ itrWillDiscardBody itr
-         unless (discardBody)
-             $ sendChunks itr wholeChunk limit
-
-         unless (Lazy.null wholeChunk)
-             $ liftIO $ atomically $
-               writeTVar (itrSentNoBodySoFar itr) False
-    where
-      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
+         liftIO $ atomically
+                $ do putTMVar (itrBodyToSend itr) (BB.fromLazyByteString str)
+                     unless (Lazy.null str)
+                         $ writeTVar (itrSentNoBodySoFar itr) False
 
 {-