Skip to content

Commit

Permalink
Handle HTTP 103 Early Hints
Browse files Browse the repository at this point in the history
  • Loading branch information
thomasjm committed Dec 19, 2023
1 parent a1057ac commit fa9a3a0
Show file tree
Hide file tree
Showing 3 changed files with 51 additions and 6 deletions.
6 changes: 6 additions & 0 deletions http-client/Network/HTTP/Client/Connection.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Network.HTTP.Client.Connection
( connectionReadLine
, connectionReadLineWith
, connectionDropTillBlankLine
, connectionUnreadLine
, dummyConnection
, openSocketConnection
, openSocketConnectionSize
Expand Down Expand Up @@ -60,6 +61,11 @@ connectionReadLineWith mhl conn bs0 =
unless (S.null y) $! connectionUnread conn y
return $! killCR $! S.concat $! front [x]

connectionUnreadLine :: Connection -> ByteString -> IO ()
connectionUnreadLine conn line = do
connectionUnread conn (S.pack [charCR, charLF])
connectionUnread conn line

charLF, charCR :: Word8
charLF = 10
charCR = 13
Expand Down
33 changes: 27 additions & 6 deletions http-client/Network/HTTP/Client/Headers.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Network.HTTP.Client.Headers
Expand Down Expand Up @@ -45,11 +47,17 @@ parseStatusHeaders mhl conn timeout' cont
Just s -> return s
Nothing -> sendBody >> getStatus

nextStatusHeaders :: IO (Maybe StatusHeaders)
nextStatusHeaders = do
(s, v) <- nextStatusLine mhl
if statusCode s == 100
then connectionDropTillBlankLine mhl conn >> return Nothing
else Just . StatusHeaders s v A.<$> parseHeaders (0 :: Int) id
if | statusCode s == 100 -> connectionDropTillBlankLine mhl conn >> return Nothing
| statusCode s == 103 -> do
linkHeaders <- parseHeadersUntilFailure 0 id
nextStatusHeaders >>= \case
Nothing -> return Nothing
Just (StatusHeaders s' v' reqHeaders) ->
return $ Just $ StatusHeaders s' v' (linkHeaders <> reqHeaders)
| otherwise -> Just . StatusHeaders s v A.<$> parseHeaders 0 id

nextStatusLine :: Maybe MaxHeaderLength -> IO (Status, HttpVersion)
nextStatusLine mhl = do
Expand Down Expand Up @@ -82,21 +90,34 @@ parseStatusHeaders mhl conn timeout' cont
Just (i, "") -> Just i
_ -> Nothing

parseHeaders :: Int -> ([Header] -> [Header]) -> IO [Header]
parseHeaders 100 _ = throwHttp OverlongHeaders
parseHeaders count front = do
line <- connectionReadLine mhl conn
if S.null line
then return $ front []
else do
mheader <- parseHeader line
case mheader of
else
parseHeader line >>= \case
Just header ->
parseHeaders (count + 1) $ front . (header:)
Nothing ->
-- Unparseable header line; rather than throwing
-- an exception, ignore it for robustness.
parseHeaders count front

parseHeadersUntilFailure :: Int -> ([Header] -> [Header]) -> IO [Header]
parseHeadersUntilFailure 100 _ = throwHttp OverlongHeaders
parseHeadersUntilFailure count front = do
line <- connectionReadLine mhl conn
if S.null line
then return $ front []
else
parseHeader line >>= \case
Just header -> parseHeadersUntilFailure (count + 1) $ front . (header:)
Nothing -> do
connectionUnreadLine conn line
return $ front []

parseHeader :: S.ByteString -> IO (Maybe Header)
parseHeader bs = do
let (key, bs2) = S.break (== charColon) bs
Expand Down
18 changes: 18 additions & 0 deletions http-client/test-nonet/Network/HTTP/Client/HeadersSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,3 +60,21 @@ spec = describe "HeadersSpec" $ do
statusHeaders `shouldBe` StatusHeaders status200 (HttpVersion 1 1) [ ("foo", "bar") ]
out >>= (`shouldBe` [])
inp >>= (`shouldBe` ["result"])

it "103 early hints" $ do
let input =
[ "HTTP/1.1 103 Early Hints\r\n"
, "Link: </foo.js>\r\n"
, "Link: </bar.js>\r\n\r\n"
, "HTTP/1.1 200 OK\r\n"
, "Content-Type: text/html\r\n\r\n"
, "<div></div>"
]
(conn, _, inp) <- dummyConnection input
statusHeaders <- parseStatusHeaders Nothing conn Nothing Nothing
statusHeaders `shouldBe` StatusHeaders status200 (HttpVersion 1 1) [
("Link", "</foo.js>")
, ("Link", "</bar.js>")
, ("Content-Type", "text/html")
]
inp >>= (`shouldBe` ["<div></div>"])

0 comments on commit fa9a3a0

Please sign in to comment.