apns-http2-0.1.1.0: Apple Push Notification service HTTP/2 integration.

Safe HaskellNone
LanguageHaskell2010

Network.Apns.Internal

Synopsis

Documentation

data ReaderEvent Source #

Event emitted by the reader thread.

Constructors

ReadFrame Frame

Reader read a well formed and not obviously wrong HTTP2 frame which is not a SETTINGS frame.

ReadSettingsUpdate Settings

Reader encountered a SETTINGS frame and updated its internal settings. The SETTINGS frame still needs to be adopted by the processor and acknowledged.

ReadH2Error ErrorCodeId ByteString ApnsTerminationReason

Reader failed to process incoming data due to some catastrophic protocol error.

Instances
Show ReaderEvent Source # 
Instance details

Defined in Network.Apns.Internal

data Context Source #

Environmental context for the processing system, passed around as a ReaderT.

Constructors

Context 

Fields

data State Source #

The dynamic state of the processing system, passed around as a StateT.

Constructors

State 

Fields

data WritableStream Source #

Data associated with a single push stream which is in the process of being written to the server as DATA frames. Streams are written as fast as flow-control windows allow, so this structure is mostly concerned with tracking that.

Constructors

WritableStream 

Fields

data ReadableStream Source #

Data associated with a stream which the processor is waiting for server frames to move along.

Constructors

StreamWaiting

So far nothing has been received from the server for the stream.

StreamReadingHeaderContinuation ByteString

A HEADERS frame without the END_HEADERS or END_STREAM flags was received, so the processor is expecting one or more CONTINUATION frames.

StreamReadingBody HeaderList ByteString

A HEADERS/CONTINUATION with END_HEADERS set but END_STREAM not set was received, so the processor is expecting zero or more DATA frames constituting the response body.

StreamReadingTrailerContinuation HeaderList ByteString ByteString

A HEADERS frame after the initial HEADERS frame and zero or more DATA frames was received with the END_STREAM flag but not the END_HEADERS flag, so the processor is expecting one or more CONTINUATION frames, the last of which will finish the stream.

type ProcessorM = ExceptT ApnsTerminationReason (StateT State (ReaderT Context IO)) Source #

The monad stack used within the processing system.

processorDebug :: (MonadReader Context m, MonadIO m) => Text -> m () Source #

Emit some debug log message.

processorWrite :: EncodeInfo -> FramePayload -> ProcessorM () Source #

Enqueue a HTTP2 frame to be written. Not appropriate for HEADERSCONTINUATION as there's no guarantee of atomicity for a series of writes.

processorWriteMany :: [(EncodeInfo, FramePayload)] -> ProcessorM () Source #

Enqueue many frames to be Written as one contiguous block with no gaps, e.g. as for HEADERS/CONTINUATION sequences.

invokeWithoutException :: MonadIO m => IO () -> m () Source #

Invoke some callback function in IO where we don't care at all about exceptions.

connectApns :: forall m. MonadIO m => ApnsConnectionParams -> m (Either ApnsConnectionError ApnsConnection) Source #

Establish a single connection to APNs, yielding Right ApnsConnection on success, Left ApnsConnectionError otherwise.

processor :: ApnsConnectionParams -> Context -> Socket -> IO (Either ApnsConnectionError ApnsConnection) Source #

Main processing for an APNs connection which sets up the reading and writing threads for exchanging HTTP/2 frames over an established TLS connection, finishes the HTTP/2 connection initiation, and then forks off the asynchronous processing.

writePhase :: ProcessorM () Source #

Perform the write phase, writing as many DATA frames as the flow-control windows will allow us

postWritePhase :: Bool -> ProcessorM () Source #

Perform the post-write phase, where incoming messages, work, and other state changes are processed prior to returning to the write phase

at this point one of the following conditions is true: the connection flow control window has been exhausted, all stream flow-control windows have been exhausted, all streams have been written out and are waiting for a server response, or there are no pending pushes so now we wait for one of the following things to happen: an incoming SETTINGS frame, which we need to adopt and might change the initial window size and thus all flow-control windows an incoming WINDOW_UPDATE frame, which expands one of the flow-control windows a PING frame which we respond to immediately a PRIORITY frame which we ignore a PUSH_PROMISE frame which we complain about mightily a HEADERSCONTINUATIONDATA/RST_STREAM frame which advances the read state of some stream a GOAWAY frame which causes us to go into the closing state and signal any dropped pushes as dropped

The Bool argument indicates whether this postWritePhase follows another post write phase which either adjusted flow-control windows or added streams and thus controls whether this should block waiting for more to do or can immediately enter a write phase as soon as other work has been handled.

processReaderEvent :: Bool -> ReaderEvent -> ProcessorM () Source #

Process a reader event in the postWritePhase. This boils down to propagating a failure if the reader failed, adopting and acknowleding new settings if the reader received and processed a SETTINGS frame, or case switching on the received frame and doing various state things based on the frame.

The Bool is the haveUpdatedWindowsOrStreams flag propagating for this postWritePhase

processUpdatedSettings :: Settings -> ProcessorM Bool Source #

Do the work required when receiving new settings from the server, such as acknowledging the update. This is a separate function since it's used both by the preface and the receive frame processing. Yields True iff the window sizes were updated.

processReadFrame :: Bool -> Frame -> ProcessorM () Source #

Process an incoming frame which is not a SETTINGS frame.

processNewPush :: Bool -> ApnsPush -> ProcessorM () Source #

Process a new ApnsPush by allocating a stream for it, sending its headers, and preparing to write the body data for it, then continuing on with the postWritePhase in progress.

headersForPush :: ByteString -> ApnsPush -> HeaderList Source #

Given an ApnsPush, compose the list of headers that should be sent for it.

encodeHeaderBlockFragments :: Int -> DynamicTable -> HeaderList -> IO [HeaderBlockFragment] Source #

Given the maximum frame size, a HeaderList, and the DynamicTable for encoding, encode a list of headers into a list of header block fragments. The first such fragment gets sent in a HEADERS frame while the subsequent ones if any get sent in a CONTINUATION frame.

reader :: (Text -> IO ()) -> Context -> Socket -> TBMQueue ReaderEvent -> IO () Source #

Reader thread. Before this exits, some debug log will be emitted, the socket will be shut down for reads, and the reader queue will be closed.

writer :: (Text -> IO ()) -> Context -> Socket -> TBMQueue (EncodeInfo, FramePayload) -> IO () Source #

Writer thread. Before this exits, some debug log will be emitted, the socket will be shut down for writes, and the writer queue will be closed.