File: ClientSpec.hs

package info (click to toggle)
haskell-http-client 0.7.17-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 528 kB
  • sloc: haskell: 4,029; makefile: 3
file content (281 lines) | stat: -rw-r--r-- 11,382 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Network.HTTP.ClientSpec where

import           Control.Concurrent        (threadDelay, yield)
import           Control.Concurrent.Async  (withAsync)
import qualified Control.Concurrent.Async  as Async
import           Control.Exception         (bracket, throwIO, ErrorCall(..))
import qualified Control.Exception         as E
import           Control.Monad             (forever, replicateM_, when, unless)
import           Network.HTTP.Client       hiding (port)
import qualified Network.HTTP.Client       as NC
import qualified Network.HTTP.Client.Internal as Internal
import           Network.HTTP.Types        (status413)
import           Network.HTTP.Types.Header
import qualified Network.Socket            as NS
import           Test.Hspec
import qualified Data.Streaming.Network    as N
import qualified Data.ByteString           as S
import qualified Data.ByteString.Lazy      as SL
import           Data.ByteString.Lazy.Char8 () -- orphan instance
import           Data.IORef
import           System.Mem                (performGC)

-- See: https://github.com/snoyberg/http-client/issues/111#issuecomment-366526660
notWindows :: Monad m => m () -> m ()
#ifdef WINDOWS
notWindows _ = return ()
#else
notWindows x = x
#endif

main :: IO ()
main = hspec spec

silentIOError :: IO () -> IO ()
silentIOError a = a `E.catch` \e -> do
  let _ = e :: IOError
  return ()


redirectServer :: Maybe Int
               -- ^ If Just, stop redirecting after that many hops.
               -> (Int -> IO a) -> IO a
redirectServer maxRedirects inner = bracket
    (N.bindRandomPortTCP "*4")
    (NS.close . snd)
    $ \(port, lsocket) -> withAsync
        (N.runTCPServer (N.serverSettingsTCPSocket lsocket) app)
        (const $ inner port)
  where
    redirect ad = do
        N.appWrite ad "HTTP/1.1 301 Redirect\r\nLocation: /\r\ncontent-length: 5\r\n\r\n"
        threadDelay 10000
        N.appWrite ad "hello\r\n"
        threadDelay 10000
    app ad = Async.race_
        (silentIOError $ forever (N.appRead ad))
        (silentIOError $ case maxRedirects of
            Nothing -> forever $ redirect ad
            Just n ->
              replicateM_ n (redirect ad) >>
              N.appWrite ad "HTTP/1.1 200 OK\r\ncontent-length: 5\r\n\r\nhello\r\n")

redirectCloseServer :: (Int -> IO a) -> IO a
redirectCloseServer inner = bracket
    (N.bindRandomPortTCP "*4")
    (NS.close . snd)
    $ \(port, lsocket) -> withAsync
        (N.runTCPServer (N.serverSettingsTCPSocket lsocket) app)
        (const $ inner port)
  where
    app ad = do
      Async.race_
          (silentIOError $ forever (N.appRead ad))
          (silentIOError $ N.appWrite ad "HTTP/1.1 301 Redirect\r\nLocation: /\r\nConnection: close\r\n\r\nhello")
      case N.appRawSocket ad of
        Nothing -> error "appRawSocket failed"
        Just s -> NS.shutdown s NS.ShutdownSend

bad100Server :: Bool -- ^ include extra headers?
             -> (Int -> IO a) -> IO a
bad100Server extraHeaders inner = bracket
    (N.bindRandomPortTCP "*4")
    (NS.close . snd)
    $ \(port, lsocket) -> withAsync
        (N.runTCPServer (N.serverSettingsTCPSocket lsocket) app)
        (const $ inner port)
  where
    app ad = Async.race_
        (silentIOError $ forever $ N.appRead ad)
        (silentIOError $ forever $ do
            N.appWrite ad $ S.concat
                [ "HTTP/1.1 100 Continue\r\n"
                , if extraHeaders then "foo:bar\r\nbaz: bin\r\n" else ""
                , "\r\nHTTP/1.1 200 OK\r\ncontent-length: 5\r\n\r\nhello\r\n"
                ]
            threadDelay 10000)

earlyClose413 :: (Int -> IO a) -> IO a
earlyClose413 inner = bracket
    (N.bindRandomPortTCP "*4")
    (NS.close . snd)
    $ \(port, lsocket) -> withAsync
        (N.runTCPServer (N.serverSettingsTCPSocket lsocket) app)
        (const $ inner port)
  where
    app ad = silentIOError $ do
        let readHeaders front = do
                newBS <- N.appRead ad
                let bs = S.append front newBS
                if "\r\n\r\n" `S.isInfixOf` bs
                    then return ()
                    else readHeaders bs
        readHeaders S.empty
        N.appWrite ad "HTTP/1.1 413 Too Large\r\ncontent-length: 7\r\n\r\ngoodbye"

-- Make sure we detect bad situations like
-- https://github.com/yesodweb/wai/issues/346 better than we did previously, so
-- that misreporting like https://github.com/snoyberg/http-client/issues/108
-- doesn't occur.
lengthAndChunked :: (Int -> IO a) -> IO a
lengthAndChunked = serveWith "HTTP/1.1 200 OK\r\ncontent-length: 24\r\ntransfer-encoding: chunked\r\n\r\n4\r\nWiki\r\n5\r\npedia\r\ne\r\n in\r\n\r\nchunks.\r\n0\r\n\r\n"

lengthZeroAndChunked :: (Int -> IO a) -> IO a
lengthZeroAndChunked = serveWith "HTTP/1.1 200 OK\r\ncontent-length: 0\r\ntransfer-encoding: chunked\r\n\r\n4\r\nWiki\r\n5\r\npedia\r\ne\r\n in\r\n\r\nchunks.\r\n0\r\n\r\n"

lengthZeroAndChunkZero :: (Int -> IO a) -> IO a
lengthZeroAndChunkZero = serveWith "HTTP/1.1 200 OK\r\ncontent-length: 0\r\ntransfer-encoding: chunked\r\n\r\n0\r\n\r\n"

serveWith :: S.ByteString -> (Int -> IO a) -> IO a
serveWith resp inner = do
  (port, lsocket) <- (N.bindRandomPortTCP "*4")
  res <- Async.race
    (N.runTCPServer (N.serverSettingsTCPSocket lsocket) app)
    (inner port)
  case res of
    Left () -> error $ "serveWith: got Left"
    Right x -> return x
  where
    app ad = silentIOError $ do
        let readHeaders front = do
                newBS <- N.appRead ad
                let bs = S.append front newBS
                if "\r\n\r\n" `S.isInfixOf` bs
                    then return ()
                    else readHeaders bs
        readHeaders S.empty
        N.appWrite ad resp

getChunkedResponse :: Int -> Manager -> IO (Response SL.ByteString)
getChunkedResponse port' man = flip httpLbs man "http://localhost"
  { NC.port     = port'
  , requestBody = RequestBodyStreamChunked ($ return (S.replicate 100000 65))
  }

spec :: Spec
spec = describe "Client" $ do
    describe "fails on empty hostnames #40" $ do
        let test url = it url $ do
                req <- parseUrlThrow url
                man <- newManager defaultManagerSettings
                _ <- httpLbs req man `shouldThrow` \e ->
                    case e of
                        HttpExceptionRequest _ (InvalidDestinationHost "") -> True
                        _ -> False
                return ()
        mapM_ test ["http://", "https://", "http://:8000", "https://:8001"]
    it "headers can be stripped on redirect" $ redirectServer (Just 5) $ \port -> do
        req' <- parseUrlThrow $ "http://127.0.0.1:" ++ show port
        let req = req' { requestHeaders = [(hAuthorization, "abguvatgbfrrurer")]
                       , redirectCount = 10
                       , shouldStripHeaderOnRedirect = (== hAuthorization)
                       }
        man <- newManager defaultManagerSettings
        withResponseHistory req man $ \hr -> do
          print $ map (requestHeaders . fst) $ hrRedirects hr
          mapM_ (\r -> requestHeaders r `shouldBe` []) $
            map fst $ tail $ hrRedirects hr
    it "redirecting #41" $ redirectServer Nothing $ \port -> do
        req' <- parseUrlThrow $ "http://127.0.0.1:" ++ show port
        let req = req' { redirectCount = 1 }
        man <- newManager defaultManagerSettings
        replicateM_ 10 $ do
            httpLbs req man `shouldThrow` \e ->
                case e of
                    HttpExceptionRequest _ (TooManyRedirects _) -> True
                    _ -> False
    it "redirectCount=0" $ redirectServer Nothing $ \port -> do
        req' <- parseUrlThrow $ "http://127.0.0.1:" ++ show port
        let req = req' { redirectCount = 0 }
        man <- newManager defaultManagerSettings
        replicateM_ 10 $ do
            httpLbs req man `shouldThrow` \e ->
                case e of
                    HttpExceptionRequest _ StatusCodeException{} -> True
                    _ -> False
    it "connecting to missing server gives nice error message" $ do
        (port, socket) <- N.bindRandomPortTCP "*4"
        NS.close socket
        req <- parseUrlThrow $ "http://127.0.0.1:" ++ show port
        man <- newManager defaultManagerSettings
        httpLbs req man `shouldThrow` \e ->
            case e of
                HttpExceptionRequest req' (ConnectionFailure _)
                    -> host req == host req'
                    && NC.port req == NC.port req'
                _ -> False

    describe "extra headers after 100 #49" $ do
        let test x = it (show x) $ bad100Server x $ \port -> do
                req <- parseUrlThrow $ "http://127.0.0.1:" ++ show port
                man <- newManager defaultManagerSettings
                replicateM_ 10 $ do
                    x' <- httpLbs req man
                    responseBody x' `shouldBe` "hello"
        test False
        test True

    notWindows $ it "early close on a 413" $ earlyClose413 $ \port' -> do
        man <- newManager defaultManagerSettings
        res <- getChunkedResponse port' man
        responseBody res `shouldBe` "goodbye"
        responseStatus res `shouldBe` status413

    notWindows $ it "length zero and chunking zero #108" $ lengthZeroAndChunkZero $ \port' -> do
        man <- newManager defaultManagerSettings
        res <- getChunkedResponse port' man
        responseBody res `shouldBe` ""

    notWindows $ it "length zero and chunking" $ lengthZeroAndChunked $ \port' -> do
        man <- newManager defaultManagerSettings
        res <- getChunkedResponse port' man
        responseBody res `shouldBe` "Wikipedia in\r\n\r\nchunks."

    notWindows $ it "length and chunking" $ lengthAndChunked $ \port' -> do
        man <- newManager defaultManagerSettings
        res <- getChunkedResponse port' man
        responseBody res `shouldBe` "Wikipedia in\r\n\r\nchunks."

    notWindows $ it "withResponseHistory and redirect" $ redirectCloseServer $ \port -> do
        -- see https://github.com/snoyberg/http-client/issues/169
        req' <- parseUrlThrow $ "http://127.0.0.1:" ++ show port
        let req = req' {redirectCount = 1}
        man <- newManager defaultManagerSettings
        withResponseHistory req man (const $ return ())
          `shouldThrow` \e ->
              case e of
              HttpExceptionRequest _ (TooManyRedirects _) -> True
              _ -> False

    it "should not write to closed connection" $ do
        -- see https://github.com/snoyberg/http-client/issues/225
        closedRef <- newIORef False
        okRef <- newIORef True
        let checkStatus = do
              closed <- readIORef closedRef
              when closed $ do
                writeIORef okRef False

        conn <- makeConnection
          (return S.empty)
          (const checkStatus)
          (checkStatus >> writeIORef closedRef True)

        Internal.connectionClose conn

        -- let GC release the connection and run finalizers
        performGC
        yield
        performGC

        ok <- readIORef okRef
        unless ok $
          throwIO (ErrorCall "already closed")

    it "does not allow port overflow #383" $ do
      case parseRequest "https://o_O:18446744072699450606" of
        Left _ -> pure () :: IO ()
        Right req -> error $ "Invalid request: " ++ show req