2020-10-16 15:06:44 +03:00
|
|
|
{-|
|
|
|
|
KingSubsite: runtime-exclusive HTTP request handling, for /~_~
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Urbit.Vere.Eyre.KingSubsite
|
|
|
|
( KingSubsite
|
|
|
|
, kingSubsite
|
|
|
|
, runKingSubsite
|
|
|
|
, fourOhFourSubsite
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Urbit.Prelude hiding (Builder)
|
|
|
|
|
|
|
|
import Data.ByteString.Builder
|
2020-10-28 21:56:03 +03:00
|
|
|
import Urbit.King.Scry
|
2020-10-16 15:06:44 +03:00
|
|
|
|
|
|
|
import Data.Conduit (ConduitT, Flush(..), yield)
|
|
|
|
import Data.Text.Encoding (encodeUtf8Builder)
|
2020-12-04 10:12:14 +03:00
|
|
|
import Urbit.Vere.Stat (RenderedStat)
|
2020-10-16 15:06:44 +03:00
|
|
|
|
2020-10-28 21:33:21 +03:00
|
|
|
import qualified Data.Text.Encoding as E
|
2020-10-16 15:06:44 +03:00
|
|
|
import qualified Network.HTTP.Types as H
|
|
|
|
import qualified Network.Wai as W
|
|
|
|
import qualified Network.Wai.Conduit as W
|
|
|
|
|
|
|
|
newtype KingSubsite = KS { runKingSubsite :: W.Application }
|
|
|
|
|
|
|
|
data SlogAction
|
|
|
|
= KeepAlive
|
|
|
|
| Slog (Atom, Tank)
|
|
|
|
|
2020-10-21 02:42:20 +03:00
|
|
|
streamSlog :: Monad m => SlogAction -> ConduitT () (Flush Builder) m ()
|
|
|
|
streamSlog a = do
|
2020-10-16 15:06:44 +03:00
|
|
|
case a of
|
|
|
|
KeepAlive -> pure ()
|
|
|
|
Slog (_, t) -> for_ (wash (WashCfg 0 80) (tankTree t)) $ \l -> do
|
|
|
|
yield $ Chunk "data:"
|
|
|
|
yield $ Chunk $ encodeUtf8Builder $ unTape l
|
|
|
|
yield $ Chunk "\n"
|
|
|
|
yield $ Chunk "\n"
|
|
|
|
yield $ Flush
|
|
|
|
|
|
|
|
kingSubsite :: HasLogFunc e
|
2020-10-28 21:33:21 +03:00
|
|
|
=> Ship
|
2020-12-19 04:00:56 +03:00
|
|
|
-> ScryFunc
|
2020-12-04 10:12:14 +03:00
|
|
|
-> IO RenderedStat
|
2020-10-28 21:33:21 +03:00
|
|
|
-> TVar ((Atom, Tank) -> IO ())
|
2020-10-16 15:06:44 +03:00
|
|
|
-> RAcquire e KingSubsite
|
2020-12-04 10:12:14 +03:00
|
|
|
kingSubsite who scry stat func = do
|
2020-10-21 02:42:20 +03:00
|
|
|
clients <- newTVarIO (mempty :: Map Word (SlogAction -> IO ()))
|
|
|
|
nextId <- newTVarIO (0 :: Word)
|
|
|
|
baton <- newTMVarIO ()
|
2020-10-28 21:33:21 +03:00
|
|
|
env <- ask
|
2020-10-21 02:42:20 +03:00
|
|
|
|
|
|
|
atomically $ writeTVar func $ \s -> readTVarIO clients >>= traverse_ ($ Slog s)
|
|
|
|
|
2020-10-16 15:06:44 +03:00
|
|
|
acquireWorker "Runtime subsite keep-alive" $ forever $ do
|
|
|
|
threadDelay 20_000_000
|
2020-10-21 02:42:20 +03:00
|
|
|
io $ readTVarIO clients >>= traverse_ ($ KeepAlive)
|
2020-10-16 15:06:44 +03:00
|
|
|
|
2020-10-21 02:42:20 +03:00
|
|
|
pure $ KS $ \req respond -> case W.pathInfo req of
|
2020-10-31 23:00:00 +03:00
|
|
|
["~_~", "slog"] -> bracket
|
2020-10-21 02:42:20 +03:00
|
|
|
(do
|
|
|
|
id <- atomically $ do
|
|
|
|
id <- readTVar nextId
|
|
|
|
modifyTVar' nextId (+ 1)
|
|
|
|
pure id
|
|
|
|
slogQ <- newTQueueIO
|
|
|
|
atomically $
|
|
|
|
modifyTVar' clients (insertMap id (atomically . writeTQueue slogQ))
|
|
|
|
pure (id, slogQ))
|
|
|
|
(\(id, _) -> atomically $ modifyTVar' clients (deleteMap id))
|
2020-10-28 21:33:21 +03:00
|
|
|
(\(_, q) -> do
|
|
|
|
authed <- authenticated env req
|
2020-10-31 01:42:33 +03:00
|
|
|
if not authed
|
|
|
|
then respond $ emptyResponse 403 "Permission Denied"
|
|
|
|
else
|
2020-10-31 23:00:00 +03:00
|
|
|
let loop = yield Flush
|
|
|
|
>> forever (atomically (readTQueue q) >>= streamSlog)
|
2020-12-04 10:12:14 +03:00
|
|
|
in respond $ W.responseSource (H.mkStatus 200 "OK") slogHeads loop)
|
|
|
|
|
|
|
|
["~_~", "stat"] -> do
|
|
|
|
authed <- authenticated env req
|
|
|
|
if not authed
|
|
|
|
then respond $ emptyResponse 403 "Permission Denied"
|
|
|
|
else do
|
|
|
|
lines <- stat
|
|
|
|
let msg = mconcat ((<> "\n") . encodeUtf8Builder <$> lines)
|
|
|
|
<> "\nRefresh for more current data."
|
|
|
|
respond $ W.responseBuilder (H.mkStatus 200 "OK") statHeads msg
|
2020-10-16 15:06:44 +03:00
|
|
|
|
2020-10-31 01:42:33 +03:00
|
|
|
_ -> respond $ emptyResponse 404 "Not Found"
|
2020-10-16 15:06:44 +03:00
|
|
|
|
2020-10-21 02:42:20 +03:00
|
|
|
where
|
2020-12-04 10:12:14 +03:00
|
|
|
slogHeads = [ ("Content-Type", "text/event-stream")
|
|
|
|
, ("Cache-Control", "no-cache")
|
|
|
|
, ("Connection", "keep-alive")
|
|
|
|
]
|
|
|
|
|
|
|
|
statHeads = [ ("Content-Type", "text/plain")
|
|
|
|
, ("Cache-Control", "no-cache")
|
|
|
|
]
|
2020-10-16 15:06:44 +03:00
|
|
|
|
2020-10-31 01:42:33 +03:00
|
|
|
emptyResponse cod mes = W.responseLBS (H.mkStatus cod mes) [] ""
|
|
|
|
|
2020-10-28 21:33:21 +03:00
|
|
|
authenticated env req = runRIO env
|
|
|
|
$ (scryAuth $ getCookie req)
|
|
|
|
>>= pure . fromMaybe False
|
|
|
|
|
|
|
|
getCookie req = intercalate "; "
|
|
|
|
$ fmap (E.decodeUtf8 . snd)
|
|
|
|
$ filter ((== "cookie") . fst)
|
2020-10-31 23:00:00 +03:00
|
|
|
$ W.requestHeaders req
|
2020-10-28 21:33:21 +03:00
|
|
|
|
|
|
|
scryAuth :: HasLogFunc e
|
|
|
|
=> Text
|
|
|
|
-> RIO e (Maybe Bool)
|
|
|
|
scryAuth cookie =
|
2021-03-02 22:19:48 +03:00
|
|
|
scryNow scry "ex" "" ["authenticated", "cookie", textAsT cookie]
|
2020-10-28 21:33:21 +03:00
|
|
|
|
2020-10-16 15:06:44 +03:00
|
|
|
fourOhFourSubsite :: Ship -> KingSubsite
|
|
|
|
fourOhFourSubsite who = KS $ \req respond ->
|
|
|
|
respond $ W.responseLBS (H.mkStatus 404 "Not Found") [] body
|
|
|
|
where
|
|
|
|
body = toLazyByteString $ foldMap charUtf8 $ msg
|
2020-10-31 01:42:33 +03:00
|
|
|
msg = "Ship " <> show who <> " not docked."
|