{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE RankNTypes #-}
module Network.HTTP2.Client.FrameConnection (
Http2FrameConnection(..)
, newHttp2FrameConnection
, Http2ServerStream(..)
, Http2FrameClientStream(..)
, makeFrameClientStream
, sendOne
, sendBackToBack
, next
, closeConnection
) where
import Control.DeepSeq (deepseq)
import Control.Exception.Lifted (bracket)
import Control.Concurrent.MVar.Lifted (newMVar, takeMVar, putMVar)
import Control.Monad ((>=>), void, when)
import qualified Data.ByteString as ByteString
import Network.HTTP2 (FrameHeader(..), FrameFlags, FramePayload, HTTP2Error, encodeInfo, decodeFramePayload)
import qualified Network.HTTP2 as HTTP2
import Network.Socket (HostName, PortNumber)
import qualified Network.TLS as TLS
import Network.HTTP2.Client.Exceptions
import Network.HTTP2.Client.RawConnection
data Http2FrameConnection = Http2FrameConnection {
_makeFrameClientStream :: HTTP2.StreamId -> Http2FrameClientStream
, _serverStream :: Http2ServerStream
, _closeConnection :: ClientIO ()
}
closeConnection :: Http2FrameConnection -> ClientIO ()
closeConnection = _closeConnection
makeFrameClientStream :: Http2FrameConnection
-> HTTP2.StreamId
-> Http2FrameClientStream
makeFrameClientStream = _makeFrameClientStream
data Http2FrameClientStream = Http2FrameClientStream {
_sendFrames :: ClientIO [(FrameFlags -> FrameFlags, FramePayload)] -> ClientIO ()
, _getStreamId :: HTTP2.StreamId
}
sendOne :: Http2FrameClientStream -> (FrameFlags -> FrameFlags) -> FramePayload -> ClientIO ()
sendOne client f payload = _sendFrames client (pure [(f, payload)])
sendBackToBack :: Http2FrameClientStream -> [(FrameFlags -> FrameFlags, FramePayload)] -> ClientIO ()
sendBackToBack client payloads = _sendFrames client (pure payloads)
data Http2ServerStream = Http2ServerStream {
_nextHeaderAndFrame :: ClientIO (FrameHeader, Either HTTP2Error FramePayload)
}
next :: Http2FrameConnection -> ClientIO (FrameHeader, Either HTTP2Error FramePayload)
next = _nextHeaderAndFrame . _serverStream
frameHttp2RawConnection
:: RawHttp2Connection
-> ClientIO Http2FrameConnection
frameHttp2RawConnection http2conn = do
writerMutex <- newMVar ()
let writeProtect io =
bracket (takeMVar writerMutex) (putMVar writerMutex) (const io)
let makeClientStream streamID =
let putFrame modifyFF frame =
let info = encodeInfo modifyFF streamID
in HTTP2.encodeFrame info frame
putFrames f = writeProtect . void $ do
xs <- f
let ys = fmap (uncurry putFrame) xs
deepseq ys (_sendRaw http2conn ys)
in Http2FrameClientStream putFrames streamID
nextServerFrameChunk = Http2ServerStream $ do
b9 <- _nextRaw http2conn 9
when (ByteString.length b9 /= 9) $ throwError $ EarlyEndOfStream
let (fTy, fh@FrameHeader{..}) = HTTP2.decodeFrameHeader b9
let decoder = decodeFramePayload fTy
buf <- _nextRaw http2conn payloadLength
when (ByteString.length buf /= payloadLength) $ throwError $ EarlyEndOfStream
let nf = decoder fh buf
pure (fh, nf)
gtfo = _close http2conn
return $ Http2FrameConnection makeClientStream nextServerFrameChunk gtfo
newHttp2FrameConnection :: HostName
-> PortNumber
-> Maybe TLS.ClientParams
-> ClientIO Http2FrameConnection
newHttp2FrameConnection host port params = do
frameHttp2RawConnection =<< newRawHttp2Connection host port params