{-# LANGUAGE CPP #-}
module Network.Wai.Handler.Warp.Conduit where
import Control.Exception
import qualified Data.ByteString as S
import qualified Data.IORef as I
import Network.Wai.Handler.Warp.Imports
import Network.Wai.Handler.Warp.Types
data ISource = ISource !Source !(I.IORef Int)
mkISource :: Source -> Int -> IO ISource
mkISource src cnt = do
ref <- I.newIORef cnt
return $! ISource src ref
readISource :: ISource -> IO ByteString
readISource (ISource src ref) = do
count <- I.readIORef ref
if count == 0
then return S.empty
else do
bs <- readSource src
when (S.null bs) $ throwIO ConnectionClosedByPeer
let
toSend = min count (S.length bs)
count' = count - toSend
case () of
()
| count' > 0 -> do
I.writeIORef ref count'
return bs
| otherwise -> do
let (x, y) = S.splitAt toSend bs
leftoverSource src y
assert (count' == 0) $ I.writeIORef ref count'
return x
data CSource = CSource !Source !(I.IORef ChunkState)
data ChunkState = NeedLen
| NeedLenNewline
| HaveLen Word
| DoneChunking
deriving Show
mkCSource :: Source -> IO CSource
mkCSource src = do
ref <- I.newIORef NeedLen
return $! CSource src ref
readCSource :: CSource -> IO ByteString
readCSource (CSource src ref) = do
mlen <- I.readIORef ref
go mlen
where
withLen 0 bs = do
leftoverSource src bs
dropCRLF
yield' S.empty DoneChunking
withLen len bs
| S.null bs = do
I.writeIORef ref DoneChunking
return S.empty
| otherwise =
case S.length bs `compare` fromIntegral len of
EQ -> yield' bs NeedLenNewline
LT -> yield' bs $ HaveLen $ len - fromIntegral (S.length bs)
GT -> do
let (x, y) = S.splitAt (fromIntegral len) bs
leftoverSource src y
yield' x NeedLenNewline
yield' bs mlen = do
I.writeIORef ref mlen
return bs
dropCRLF = do
bs <- readSource src
case S.uncons bs of
Nothing -> return ()
Just (13, bs') -> dropLF bs'
Just (10, bs') -> leftoverSource src bs'
Just _ -> leftoverSource src bs
dropLF bs =
case S.uncons bs of
Nothing -> do
bs2 <- readSource' src
unless (S.null bs2) $ dropLF bs2
Just (10, bs') -> leftoverSource src bs'
Just _ -> leftoverSource src bs
go NeedLen = getLen
go NeedLenNewline = dropCRLF >> getLen
go (HaveLen 0) = do
dropCRLF
I.writeIORef ref DoneChunking
return S.empty
go (HaveLen len) = do
bs <- readSource src
withLen len bs
go DoneChunking = return S.empty
getLen = do
bs <- readSource src
if S.null bs
then do
I.writeIORef ref $ assert False $ HaveLen 0
return S.empty
else do
(x, y) <-
case S.break (== 10) bs of
(x, y)
| S.null y -> do
bs2 <- readSource' src
return $ if S.null bs2
then (x, y)
else S.break (== 10) $ bs `S.append` bs2
| otherwise -> return (x, y)
let w =
S.foldl' (\i c -> i * 16 + fromIntegral (hexToWord c)) 0
$ S.takeWhile isHexDigit x
let y' = S.drop 1 y
y'' <-
if S.null y'
then readSource src
else return y'
withLen w y''
hexToWord w
| w < 58 = w - 48
| w < 71 = w - 55
| otherwise = w - 87
isHexDigit :: Word8 -> Bool
isHexDigit w = w >= 48 && w <= 57
|| w >= 65 && w <= 70
|| w >= 97 && w <= 102