-- |
--     A WAI adapter to the HTML5 Server-Sent Events API.
--
--     If running through a proxy like Nginx you might need to add the
--     headers:
--
--     > [ ("X-Accel-Buffering", "no"), ("Cache-Control", "no-cache")]
--
--     There is a small example using these functions in the @example@ directory.
module Network.Wai.EventSource (
    ServerEvent (..),
    eventSourceAppChan,
    eventSourceAppIO,
    eventStreamAppRaw,
) where

import Control.Concurrent.Chan (Chan, dupChan, readChan)
import Control.Monad.IO.Class (liftIO)
import Data.Function (fix)
import Network.HTTP.Types (hContentType, status200)
import Network.Wai (Application, responseStream)

import Network.Wai.EventSource.EventStream

-- | Make a new WAI EventSource application reading events from
-- the given channel.
eventSourceAppChan :: Chan ServerEvent -> Application
eventSourceAppChan :: Chan ServerEvent -> Application
eventSourceAppChan Chan ServerEvent
chan Request
req Response -> IO ResponseReceived
sendResponse = do
    Chan ServerEvent
chan' <- IO (Chan ServerEvent) -> IO (Chan ServerEvent)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Chan ServerEvent) -> IO (Chan ServerEvent))
-> IO (Chan ServerEvent) -> IO (Chan ServerEvent)
forall a b. (a -> b) -> a -> b
$ Chan ServerEvent -> IO (Chan ServerEvent)
forall a. Chan a -> IO (Chan a)
dupChan Chan ServerEvent
chan
    IO ServerEvent -> Application
eventSourceAppIO (Chan ServerEvent -> IO ServerEvent
forall a. Chan a -> IO a
readChan Chan ServerEvent
chan') Request
req Response -> IO ResponseReceived
sendResponse

-- | Make a new WAI EventSource application reading events from
-- the given IO action.
eventSourceAppIO :: IO ServerEvent -> Application
eventSourceAppIO :: IO ServerEvent -> Application
eventSourceAppIO IO ServerEvent
src Request
_ Response -> IO ResponseReceived
sendResponse =
    Response -> IO ResponseReceived
sendResponse
        (Response -> IO ResponseReceived)
-> Response -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ Status -> ResponseHeaders -> StreamingBody -> Response
responseStream
            Status
status200
            [(HeaderName
hContentType, ByteString
"text/event-stream")]
        (StreamingBody -> Response) -> StreamingBody -> Response
forall a b. (a -> b) -> a -> b
$ \Builder -> IO ()
sendChunk IO ()
flush -> do
            IO ()
flush
            (IO () -> IO ()) -> IO ()
forall a. (a -> a) -> a
fix ((IO () -> IO ()) -> IO ()) -> (IO () -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IO ()
loop -> do
                ServerEvent
se <- IO ServerEvent
src
                case ServerEvent -> Maybe Builder
eventToBuilder ServerEvent
se of
                    Maybe Builder
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                    Just Builder
b -> Builder -> IO ()
sendChunk Builder
b IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
flush IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
loop

-- | Make a new WAI EventSource application with a handler that emits events.
--
-- @since 3.0.28
eventStreamAppRaw :: ((ServerEvent -> IO ()) -> IO () -> IO ()) -> Application
eventStreamAppRaw :: ((ServerEvent -> IO ()) -> IO () -> IO ()) -> Application
eventStreamAppRaw (ServerEvent -> IO ()) -> IO () -> IO ()
handler Request
_ Response -> IO ResponseReceived
sendResponse =
    Response -> IO ResponseReceived
sendResponse
        (Response -> IO ResponseReceived)
-> Response -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ Status -> ResponseHeaders -> StreamingBody -> Response
responseStream
            Status
status200
            [(HeaderName
hContentType, ByteString
"text/event-stream")]
        (StreamingBody -> Response) -> StreamingBody -> Response
forall a b. (a -> b) -> a -> b
$ \Builder -> IO ()
sendChunk IO ()
flush -> (ServerEvent -> IO ()) -> IO () -> IO ()
handler ((Builder -> IO ()) -> ServerEvent -> IO ()
forall {m :: * -> *}.
Monad m =>
(Builder -> m ()) -> ServerEvent -> m ()
sendEvent Builder -> IO ()
sendChunk) IO ()
flush
  where
    sendEvent :: (Builder -> m ()) -> ServerEvent -> m ()
sendEvent Builder -> m ()
sendChunk ServerEvent
event =
        case ServerEvent -> Maybe Builder
eventToBuilder ServerEvent
event of
            Maybe Builder
Nothing -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
            Just Builder
b -> Builder -> m ()
sendChunk Builder
b

{- HLint ignore eventStreamAppRaw "Use forM_" -}