File: Body.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 (237 lines) | stat: -rw-r--r-- 7,272 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
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiWayIf #-}
module Network.HTTP.Client.Body
    ( makeChunkedReader
    , makeLengthReader
    , makeGzipReader
    , makeUnlimitedReader
    , brConsume
    , brEmpty
    , constBodyReader
    , brReadSome
    , brRead
    ) where

import Network.HTTP.Client.Connection
import Network.HTTP.Client.Types
import Control.Exception (assert)
import Data.ByteString (empty, uncons)
import Data.IORef
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import Control.Monad (unless, when)
import qualified Data.Streaming.Zlib as Z

-- | Get a single chunk of data from the response body, or an empty
-- bytestring if no more data is available.
--
-- Note that in order to consume the entire request body, you will need to
-- repeatedly call this function until you receive an empty @ByteString@ as a
-- result.
--
-- Since 0.1.0
brRead :: BodyReader -> IO S.ByteString
brRead = id

-- | Continuously call 'brRead', building up a lazy ByteString until a chunk is
-- constructed that is at least as many bytes as requested.
--
-- Since 0.4.20
brReadSome :: BodyReader -> Int -> IO L.ByteString
brReadSome brRead' =
    loop id
  where
    loop front rem'
        | rem' <= 0 = return $ L.fromChunks $ front []
        | otherwise = do
            bs <- brRead'
            if S.null bs
                then return $ L.fromChunks $ front []
                else loop (front . (bs:)) (rem' - S.length bs)

brEmpty :: BodyReader
brEmpty = return S.empty

constBodyReader :: [S.ByteString] -> IO BodyReader
constBodyReader input = do
  iinput <- newIORef input
  return $ atomicModifyIORef iinput $ \input' ->
        case input' of
            [] -> ([], S.empty)
            x:xs -> (xs, x)

-- | Strictly consume all remaining chunks of data from the stream.
--
-- Since 0.1.0
brConsume :: BodyReader -> IO [S.ByteString]
brConsume brRead' =
    go id
  where
    go front = do
        x <- brRead'
        if S.null x
            then return $ front []
            else go (front . (x:))

makeGzipReader :: BodyReader -> IO BodyReader
makeGzipReader brRead' = do
    inf <- Z.initInflate $ Z.WindowBits 31
    istate <- newIORef Nothing
    let goPopper popper = do
            res <- popper
            case res of
                Z.PRNext bs -> do
                    writeIORef istate $ Just popper
                    return bs
                Z.PRDone -> do
                    bs <- Z.flushInflate inf
                    if S.null bs
                        then start
                        else do
                            writeIORef istate Nothing
                            return bs
                Z.PRError e -> throwHttp $ HttpZlibException e
        start = do
            bs <- brRead'
            if S.null bs
                then return S.empty
                else do
                    popper <- Z.feedInflate inf bs
                    goPopper popper
    return $ do
        state <- readIORef istate
        case state of
            Nothing -> start
            Just popper -> goPopper popper

makeUnlimitedReader
  :: IO () -- ^ cleanup
  -> Connection
  -> IO BodyReader
makeUnlimitedReader cleanup Connection {..} = do
    icomplete <- newIORef False
    return $ do
        bs <- connectionRead
        when (S.null bs) $ do
          writeIORef icomplete True
          cleanup
        return bs

makeLengthReader
  :: IO () -- ^ cleanup
  -> Int
  -> Connection
  -> IO BodyReader
makeLengthReader cleanup count0 Connection {..} = do
    icount <- newIORef count0
    return $ do
        count <- readIORef icount
        if count <= 0
            then return empty
            else do
                bs <- connectionRead
                when (S.null bs) $ throwHttp $ ResponseBodyTooShort (fromIntegral count0) (fromIntegral $ count0 - count)
                case compare count $ S.length bs of
                    LT -> do
                        let (x, y) = S.splitAt count bs
                        connectionUnread y
                        writeIORef icount (-1)
                        cleanup
                        return x
                    EQ -> do
                        writeIORef icount (-1)
                        cleanup
                        return bs
                    GT -> do
                        writeIORef icount (count - S.length bs)
                        return bs

makeChunkedReader
  :: Maybe MaxHeaderLength
  -> IO () -- ^ cleanup
  -> Bool -- ^ raw
  -> Connection
  -> IO BodyReader
makeChunkedReader mhl cleanup raw conn@Connection {..} = do
    icount <- newIORef 0
    return $ do
      bs <- go icount
      when (S.null bs) cleanup
      pure bs
  where
    go icount = do
        count0 <- readIORef icount
        (rawCount, count) <-
            if count0 == 0
                then readHeader
                else return (empty, count0)
        if count <= 0
            then do
                -- count == -1 indicates that all chunks have been consumed
                writeIORef icount (-1)
                if | count /= -1 && raw -> S.append rawCount <$> readTrailersRaw
                   | count /= -1        -> consumeTrailers *> pure empty
                   | otherwise          -> pure empty
            else do
                (bs, count') <- readChunk count
                writeIORef icount count'
                return $ appendHeader rawCount bs

    appendHeader
      | raw = S.append
      | otherwise = flip const

    readChunk 0 = return (empty, 0)
    readChunk remainder = do
        bs <- connectionRead
        when (S.null bs) $ throwHttp InvalidChunkHeaders
        case compare remainder $ S.length bs of
            LT -> do
                let (x, y) = S.splitAt remainder bs
                assert (not $ S.null y) $ connectionUnread y
                requireNewline
                done x
            EQ -> do
                requireNewline
                done bs
            GT -> return (bs, remainder - S.length bs)
      where
        done x
          | raw = return (x `S.append` "\r\n", 0)
          | otherwise = return (x, 0)

    requireNewline = do
        bs <- connectionReadLine mhl conn
        unless (S.null bs) $ throwHttp InvalidChunkHeaders

    readHeader = do
        bs <- connectionReadLine mhl conn
        case parseHex bs of
            Nothing -> throwHttp InvalidChunkHeaders
            Just hex -> return (bs `S.append` "\r\n", hex)

    parseHex bs0 =
        case uncons bs0 of
            Just (w0, bs')
                | Just i0 <- toI w0 -> Just $ parseHex' i0 bs'
            _ -> Nothing
    parseHex' i bs =
        case uncons bs of
            Just (w, bs')
                | Just i' <- toI w -> parseHex' (i * 16 + i') bs'
            _ -> i

    toI w
        | 48 <= w && w <= 57  = Just $ fromIntegral w - 48
        | 65 <= w && w <= 70  = Just $ fromIntegral w - 55
        | 97 <= w && w <= 102 = Just $ fromIntegral w - 87
        | otherwise = Nothing

    readTrailersRaw = do
        bs <- connectionReadLine mhl conn
        if S.null bs
        then pure "\r\n"
        else (bs `S.append` "\r\n" `S.append`) <$> readTrailersRaw

    consumeTrailers = connectionDropTillBlankLine mhl conn