9 module Network.HTTP.Lucu.RequestReader
13 import Control.Concurrent
14 import Control.Concurrent.STM
15 import Control.Exception hiding (block)
17 import qualified Data.Attoparsec.Lazy as LP
18 import qualified Data.ByteString as Strict
19 import qualified Data.ByteString.Lazy as Lazy
22 import Data.Monoid.Unicode
23 import qualified Data.Sequence as S
24 import qualified Data.Text as T
25 import Network.HTTP.Lucu.Abortion
26 import Network.HTTP.Lucu.Config
27 import Network.HTTP.Lucu.Chunk
28 import Network.HTTP.Lucu.HandleLike
29 import Network.HTTP.Lucu.Interaction
30 import Network.HTTP.Lucu.Preprocess
31 import Network.HTTP.Lucu.Request
32 import Network.HTTP.Lucu.Response
33 import Network.HTTP.Lucu.Resource.Internal
34 import Network.HTTP.Lucu.Resource.Tree
35 import Network.HTTP.Lucu.Utils
37 import Prelude.Unicode
38 import System.IO (hPutStrLn, stderr)
44 , cFallbacks ∷ ![FallbackHandler]
48 , cQueue ∷ !InteractionQueue
51 data ChunkReceivingState
53 | InChunk !Int -- ^Number of remaining octets in the current
54 -- chunk. It's always positive.
56 requestReader ∷ HandleLike h
65 requestReader cnf tree fbs h port addr tQueue
66 = do input ← hGetLBS h
67 acceptRequest (Context cnf tree fbs h port addr tQueue) input
69 [ Handler handleAsyncE
70 , Handler handleOthers
73 enqueue' tQueue EndOfInteraction
75 handleAsyncE ∷ AsyncException → IO ()
76 handleAsyncE ThreadKilled = return ()
77 handleAsyncE e = dump e
79 handleOthers ∷ SomeException → IO ()
82 dump ∷ Exception e ⇒ e → IO ()
84 = do hPutStrLn stderr "Lucu: requestReader caught an exception:"
85 hPutStrLn stderr $ show e
87 acceptRequest ∷ HandleLike h ⇒ Context h → Lazy.ByteString → IO ()
88 acceptRequest ctx@(Context {..}) input
90 do queue ← readTVar cQueue
91 when (S.length queue ≥ cnfMaxPipelineDepth cConfig)
92 -- Too many requests in the pipeline...
94 if Lazy.null input then
97 case LP.parse request input of
98 LP.Done input' req → acceptParsableRequest ctx req input'
99 LP.Fail _ _ _ → acceptNonparsableRequest ctx
101 acceptNonparsableRequest ∷ HandleLike h ⇒ Context h → IO ()
102 acceptNonparsableRequest ctx@(Context {..})
103 = do syi ← mkSyntacticallyInvalidInteraction cConfig
106 acceptParsableRequest ∷ HandleLike h
111 acceptParsableRequest ctx@(Context {..}) req input
112 = do let ar = preprocess (cnfServerHost cConfig) cPort req
113 if isError $ arInitialStatus ar then
114 acceptSemanticallyInvalidRequest ctx ar input
116 do rsrc ← findResource cResTree cFallbacks $ reqURI $ arRequest ar
120 arInitialStatus = fromStatusCode NotFound
122 acceptSemanticallyInvalidRequest ctx ar' input
124 → acceptRequestForResource ctx ar input path def
126 acceptSemanticallyInvalidRequest ∷ HandleLike h
131 acceptSemanticallyInvalidRequest ctx@(Context {..}) ar input
132 = do sei ← mkSemanticallyInvalidInteraction cConfig ar
134 acceptRequest ctx input
136 acceptRequestForResource ∷ HandleLike h
140 → [Strict.ByteString]
143 acceptRequestForResource ctx@(Context {..}) ar@(AugmentedRequest {..}) input rsrcPath rsrcDef
145 #if defined(HAVE_SSL)
146 cert ← hGetPeerCert cHandle
147 ni ← mkNormalInteraction cConfig cAddr cert ar rsrcPath
149 ni ← mkNormalInteraction cConfig cAddr ar rsrcPath
151 tid ← spawnRsrc rsrcDef ni
153 if reqMustHaveBody arRequest then
154 waitForReceiveBodyReq ctx ni tid input
156 acceptRequest ctx input
158 waitForReceiveBodyReq ∷ HandleLike h
164 waitForReceiveBodyReq ctx ni@(NI {..}) rsrcTid input
165 = case fromJust niReqBodyLength of
167 → waitForReceiveChunkedBodyReqForTheFirstTime ctx ni rsrcTid input
169 → waitForReceiveNonChunkedBodyReqForTheFirstTime ctx ni input len
171 -- Toooooo long name for a function...
172 waitForReceiveChunkedBodyReqForTheFirstTime ∷ HandleLike h
178 waitForReceiveChunkedBodyReqForTheFirstTime ctx ni@(NI {..}) rsrcTid input
181 do req ← takeTMVar niReceiveBodyReq
184 → do putTMVar niSendContinue niExpectedContinue
185 return $ readCurrentChunk ctx ni rsrcTid wanted input Initial
187 → do putTMVar niSendContinue False
188 return $ wasteAllChunks ctx rsrcTid input Initial
190 waitForReceiveChunkedBodyReq ∷ HandleLike h
195 → ChunkReceivingState
197 waitForReceiveChunkedBodyReq ctx ni@(NI {..}) rsrcTid input st
198 = do req ← atomically $ takeTMVar niReceiveBodyReq
201 → readCurrentChunk ctx ni rsrcTid wanted input st
203 → wasteAllChunks ctx rsrcTid input st
205 wasteAllChunks ∷ HandleLike h
209 → ChunkReceivingState
211 wasteAllChunks ctx rsrcTid = go
213 go ∷ Lazy.ByteString → ChunkReceivingState → IO ()
215 = case LP.parse chunkHeader input of
216 LP.Done input' chunkLen
217 | chunkLen ≡ 0 → gotFinalChunk input'
218 | otherwise → gotChunk input' chunkLen
220 → chunkWasMalformed rsrcTid eCtx e
221 "wasteAllChunks: chunkHeader"
222 go input (InChunk chunkLen)
223 = gotChunk input chunkLen
225 gotChunk ∷ Lazy.ByteString → Int → IO ()
226 gotChunk input chunkLen
227 = let input' = Lazy.drop (fromIntegral chunkLen) input
229 case LP.parse chunkFooter input' of
233 → chunkWasMalformed rsrcTid eCtx e
234 "wasteAllChunks: chunkFooter"
236 gotFinalChunk ∷ Lazy.ByteString → IO ()
238 = case LP.parse chunkTrailer input of
240 → acceptRequest ctx input'
242 → chunkWasMalformed rsrcTid eCtx e
243 "wasteAllChunks: chunkTrailer"
245 readCurrentChunk ∷ HandleLike h
251 → ChunkReceivingState
253 readCurrentChunk ctx ni@(NI {..}) rsrcTid wanted = go
255 go ∷ Lazy.ByteString → ChunkReceivingState → IO ()
257 = case LP.parse chunkHeader input of
258 LP.Done input' chunkLen
260 → gotFinalChunk input'
262 → gotChunk input' chunkLen
264 → chunkWasMalformed rsrcTid eCtx e
265 "readCurrentChunk: chunkHeader"
266 go input (InChunk chunkLen)
267 = gotChunk input chunkLen
269 gotChunk ∷ Lazy.ByteString → Int → IO ()
270 gotChunk input chunkLen
271 = do let bytesToRead = min wanted chunkLen
272 (block, input') = Lazy.splitAt (fromIntegral bytesToRead) input
273 block' = Strict.concat $ Lazy.toChunks block
274 actualReadBytes = Strict.length block'
275 chunkLen' = chunkLen - actualReadBytes
276 atomically $ putTMVar niReceivedBody block'
277 if chunkLen' ≡ 0 then
278 case LP.parse chunkFooter input' of
280 → waitForReceiveChunkedBodyReq ctx ni rsrcTid input'' Initial
282 → chunkWasMalformed rsrcTid eCtx e
283 "readCurrentChunk: chunkFooter"
285 waitForReceiveChunkedBodyReq ctx ni rsrcTid input' $ InChunk chunkLen'
287 gotFinalChunk ∷ Lazy.ByteString → IO ()
289 = do atomically $ putTMVar niReceivedBody (∅)
290 case LP.parse chunkTrailer input of
292 → acceptRequest ctx input'
294 → chunkWasMalformed rsrcTid eCtx e
295 "readCurrentChunk: chunkTrailer"
297 chunkWasMalformed ∷ ThreadId → [String] → String → String → IO ()
298 chunkWasMalformed tid eCtx e msg
299 = let abo = mkAbortion BadRequest [("Connection", "close")]
301 $ "chunkWasMalformed: "
304 ⊕ T.pack (intercalate ", " eCtx)
310 waitForReceiveNonChunkedBodyReqForTheFirstTime ∷ HandleLike h
316 waitForReceiveNonChunkedBodyReqForTheFirstTime ctx ni@(NI {..}) input bodyLen
319 do req ← takeTMVar niReceiveBodyReq
322 → do putTMVar niSendContinue niExpectedContinue
323 return $ readNonChunkedRequestBody ctx ni input bodyLen wanted
325 → do putTMVar niSendContinue False
326 return $ wasteNonChunkedRequestBody ctx input bodyLen
328 waitForReceiveNonChunkedBodyReq ∷ HandleLike h
334 waitForReceiveNonChunkedBodyReq ctx ni@(NI {..}) input bodyLen
335 = do req ← atomically $ takeTMVar niReceiveBodyReq
338 → readNonChunkedRequestBody ctx ni input bodyLen wanted
340 → wasteNonChunkedRequestBody ctx input bodyLen
342 wasteNonChunkedRequestBody ∷ HandleLike h
347 wasteNonChunkedRequestBody ctx input bodyLen
348 = do let input' = Lazy.drop (fromIntegral bodyLen) input
349 acceptRequest ctx input'
351 readNonChunkedRequestBody ∷ HandleLike h
358 readNonChunkedRequestBody ctx ni@(NI {..}) input bodyLen wanted
359 | bodyLen ≡ 0 = gotEndOfRequest
360 | otherwise = gotBody
364 = do let bytesToRead = min wanted bodyLen
365 (block, input') = Lazy.splitAt (fromIntegral bytesToRead) input
366 block' = Strict.concat $ Lazy.toChunks block
367 actualReadBytes = Strict.length block'
368 bodyLen' = bodyLen - actualReadBytes
369 atomically $ putTMVar niReceivedBody block'
370 waitForReceiveNonChunkedBodyReq ctx ni input' bodyLen'
372 gotEndOfRequest ∷ IO ()
374 = do atomically $ putTMVar niReceivedBody (∅)
375 acceptRequest ctx input
377 enqueue ∷ (HandleLike h, Interaction i) ⇒ Context h → i → IO ()
378 enqueue (Context {..}) = enqueue' cQueue
380 enqueue' ∷ Interaction i ⇒ InteractionQueue → i → IO ()
383 do queue ← readTVar tQueue
384 writeTVar tQueue (toInteraction itr ⊲ queue)