{-# LANGUAGE FlexibleContexts #-}
module Reflex.Backend.Wai
( WaiSource(..), newWaiSource
, waiApplicationGuest
, waiApplicationHost
, liftWaiApplication, liftWaiApplicationTagged
)
where
import Network.Wai
import Network.Wai.Internal (ResponseReceived(..))
import Control.Monad (void, forever)
import Control.Monad.Trans (MonadIO, liftIO)
import Data.Map (Map)
import qualified Data.Map as Map
import Control.Concurrent (forkIO)
import Control.Monad.STM
import Control.Concurrent.STM
import Reflex hiding (Request, Response)
data WaiSource
= WaiSource
{ wsRequest :: TMVar Request
, wsResponse :: TMVar Response
}
newWaiSource :: MonadIO m => m WaiSource
newWaiSource =
liftIO $ WaiSource <$> newEmptyTMVarIO <*> newEmptyTMVarIO
waiApplicationHost :: WaiSource -> Application
waiApplicationHost (WaiSource wReq wRes) req response = do
atomically $ putTMVar wReq req
res <- atomically $ takeTMVar wRes
response res
waiApplicationGuest ::
( Reflex t
, MonadIO m
, PerformEvent t m
, MonadIO (Performable m)
, TriggerEvent t m
) =>
WaiSource ->
(Event t Request -> m (Event t Response)) ->
m ()
waiApplicationGuest (WaiSource wReq wRes) network = do
(eReq, onReq) <- newTriggerEvent
eRes <- network eReq
performEvent_ $ liftIO . atomically . putTMVar wRes <$> eRes
void . liftIO . forkIO . forever $ do
req <- atomically $ takeTMVar wReq
onReq req
pure ()
liftWaiApplication ::
( Reflex t
, PerformEvent t m
, MonadIO (Performable m)
, TriggerEvent t m
) =>
Application ->
Event t Request ->
m (Event t Response)
liftWaiApplication app eReq = do
(eRes, onRes) <- newTriggerEvent
let go res = ResponseReceived <$ onRes res
performEvent_ $ (\req -> void . liftIO $ app req go) <$> eReq
pure eRes
liftWaiApplicationTagged ::
( Reflex t
, PerformEvent t m
, MonadIO (Performable m)
, TriggerEvent t m
) =>
Application ->
Event t (tag, Request) ->
m (Event t (Map tag Response))
liftWaiApplicationTagged app eReq = do
(eRes, onRes) <- newTriggerEvent
let go t res = ResponseReceived <$ onRes (Map.singleton t res)
performEvent_ $ (\(t, req) -> void . liftIO . app req $ go t) <$> eReq
pure eRes