diff options
author | stuebinm | 2022-08-27 01:45:12 +0200 |
---|---|---|
committer | stuebinm | 2022-08-27 01:45:12 +0200 |
commit | a4045a5b0a898042cd78eba9b22550c965a1bbd9 (patch) | |
tree | 337277b15c7fba9ea857cdd388ff1b2c84d9101b /lib/Server | |
parent | 6fa510d35f0ca8738df7274bf6f02ad75a987f60 (diff) |
controlroom: lots of pretty little knobs
(also some database schema changes, for good measure)
Diffstat (limited to '')
-rw-r--r-- | lib/Server.hs | 78 | ||||
-rw-r--r-- | lib/Server/ControlRoom.hs | 85 | ||||
-rw-r--r-- | lib/Server/GTFS_RT.hs | 20 | ||||
-rw-r--r-- | lib/Server/Util.hs | 12 |
4 files changed, 122 insertions, 73 deletions
diff --git a/lib/Server.hs b/lib/Server.hs index f7ee81b..75617bd 100644 --- a/lib/Server.hs +++ b/lib/Server.hs @@ -11,8 +11,8 @@ -- Implementation of the API. This module is the main point of the program. module Server (application) where -import Control.Monad (forever, void, when) -import Control.Monad.Extra (maybeM, whenM) +import Control.Monad (forever, unless, void, when) +import Control.Monad.Extra (maybeM, unlessM, whenM) import Control.Monad.IO.Class (MonadIO (liftIO)) import Control.Monad.Logger (logWarnN) import Control.Monad.Reader (forM) @@ -35,8 +35,9 @@ import Database.Persist import Database.Persist.Postgresql (SqlBackend, runMigration) import Fmt ((+|), (|+)) import qualified Network.WebSockets as WS -import Servant (Application, err401, err404, - serve, throwError) +import Servant (Application, + ServerError (errBody), err401, + err404, serve, throwError) import Servant.API (NoContent (..), (:<|>) (..)) import Servant.Server (Handler, hoistServer) import Servant.Swagger (toSwagger) @@ -46,7 +47,8 @@ import GTFS import Persist import Server.ControlRoom import Server.GTFS_RT (gtfsRealtimeServer) -import Server.Util (Service, ServiceM, runService) +import Server.Util (Service, ServiceM, runService, + sendErrorMsg) import Yesod (toWaiAppPlain) import System.IO.Unsafe @@ -64,11 +66,12 @@ doMigration pool = runSql pool $ runMigration migrateAll server :: GTFS -> Pool SqlBackend -> Service CompleteAPI -server gtfs@GTFS{..} dbpool = handleDebugAPI :<|> (handleStations :<|> handleTimetable :<|> handleTrip - :<|> handleRegister :<|> handleTripPing :<|> handleWS :<|> handleDebugState :<|> - gtfsRealtimeServer gtfs dbpool - :<|> adminServer gtfs dbpool) - :<|> pure (unsafePerformIO (toWaiAppPlain (ControlRoom "http://localhost:4000/cr" gtfs dbpool))) +server gtfs@GTFS{..} dbpool = handleDebugAPI + :<|> (handleStations :<|> handleTimetable :<|> handleTrip + :<|> handleRegister :<|> handleTripPing :<|> handleWS + :<|> handleDebugState :<|> handleDebugTrain :<|> handleDebugRegister + :<|> gtfsRealtimeServer gtfs dbpool) + :<|> pure (unsafePerformIO (toWaiAppPlain (ControlRoom gtfs dbpool))) where handleStations = pure stations handleTimetable station maybeDay = do -- TODO: resolve "overlay" trips (perhaps just additional CalendarDates?) @@ -80,13 +83,19 @@ server gtfs@GTFS{..} dbpool = handleDebugAPI :<|> (handleStations :<|> handleTim handleTrip trip = case M.lookup trip trips of Just res -> pure res Nothing -> throwError err404 - handleRegister tripID = do - -- TODO registration may carry extra information! + handleRegister tripID RegisterJson{..} = do + today <- liftIO getCurrentTime <&> utctDay + when (not $ runsOnDay gtfs tripID today) + $ sendErrorMsg "this trip does not run today." expires <- liftIO $ getCurrentTime <&> addUTCTime validityPeriod - RunningTripKey token <- runSql dbpool $ insert (RunningTrip expires False tripID Nothing) + RunningKey token <- runSql dbpool $ insert (Running expires False tripID today Nothing registerAgent) + pure token + handleDebugRegister tripID day = do + expires <- liftIO $ getCurrentTime <&> addUTCTime validityPeriod + RunningKey token <- runSql dbpool $ insert (Running expires False tripID day Nothing "debug key") pure token handleTripPing ping = do - lift $ checkTokenValid dbpool (coerce $ tripPingToken ping) + lift $ checkTokenValid dbpool (coerce $ trainPingToken ping) -- TODO: are these always inserted in order? runSql dbpool $ insert ping pure NoContent @@ -100,47 +109,34 @@ server gtfs@GTFS{..} dbpool = handleDebugAPI :<|> (handleStations :<|> handleTim logWarnN ("stray websocket message: "+|show msg|+" (could not decode: "+|err|+")") liftIO $ WS.sendClose conn (C8.pack err) Right ping -> do - lift $ checkTokenValid dbpool (coerce $ tripPingToken ping) + lift $ checkTokenValid dbpool (coerce $ trainPingToken ping) void $ runSql dbpool $ insert ping handleDebugState = do now <- liftIO getCurrentTime runSql dbpool $ do - running <- selectList [RunningTripBlocked ==. False, RunningTripExpires >=. now] [] - pairs <- forM running $ \(Entity token@(RunningTripKey uuid) _) -> do - entities <- selectList [TripPingToken ==. token] [] + running <- selectList [RunningBlocked ==. False, RunningExpires >=. now] [] + pairs <- forM running $ \(Entity token@(RunningKey uuid) _) -> do + entities <- selectList [TrainPingToken ==. token] [] pure (uuid, fmap entityVal entities) pure (M.fromList pairs) + handleDebugTrain tripId day = do + unless (runsOnDay gtfs tripId day) + $ sendErrorMsg ("this trip does not run on "+|day|+".") + runSql dbpool $ do + tokens <- selectList [RunningTrip ==. tripId, RunningDay ==. day] [] + pings <- forM tokens $ \(Entity token _) -> do + selectList [TrainPingToken ==. token] [] <&> fmap entityVal + pure (concat pings) handleDebugAPI = pure $ toSwagger (Proxy @API) -adminServer :: GTFS -> Pool SqlBackend -> Service AdminAPI -adminServer gtfs dbpool = - addAnnounce :<|> delAnnounce :<|> modTripDate Added Cancelled - :<|> modTripDate Cancelled Added :<|> extraTrip - where addAnnounce ann@Announcement{..} = runSql dbpool $ do - AnnouncementKey uuid <- insert ann - pure uuid - delAnnounce uuid = runSql dbpool $ do - delete (AnnouncementKey uuid) - pure NoContent - modTripDate one two tripId day = runSql dbpool $ do - getBy (TripAndDay tripId day) >>= \case - Just (Entity key (ScheduleAmendment _ _ status)) -> do - when (status == two) $ delete key - pure NoContent - Nothing -> do - insert (ScheduleAmendment tripId day one) - pure NoContent - extraTrip = error "unimplemented!" - - -- TODO: proper debug logging for expired tokens checkTokenValid :: Pool SqlBackend -> Token -> Handler () checkTokenValid dbpool token = do trip <- try $ runSql dbpool $ get (coerce token) - when (runningTripBlocked trip) + when (runningBlocked trip) $ throwError err401 - whenM (hasExpired (runningTripExpires trip)) + whenM (hasExpired (runningExpires trip)) $ throwError err401 where try m = m >>= \case Just a -> pure a diff --git a/lib/Server/ControlRoom.hs b/lib/Server/ControlRoom.hs index 9ebea42..4ef3784 100644 --- a/lib/Server/ControlRoom.hs +++ b/lib/Server/ControlRoom.hs @@ -28,7 +28,7 @@ import qualified Data.Map as M import Data.Pool (Pool) import Data.Text (Text) import qualified Data.Text as T -import Data.Time (getCurrentTime, utctDay) +import Data.Time (UTCTime, getCurrentTime, utctDay) import Data.Time.Calendar (Day) import Data.Time.Format.ISO8601 (iso8601Show) import Data.UUID (UUID) @@ -40,13 +40,9 @@ import Database.Persist.Sql (PersistFieldSql, SqlBackend, runSqlPool) import Fmt ((+|), (|+)) import GHC.Generics (Generic) -import Persist (AmendmentStatus, Announcement (..), - EntityField (..), Key (..), - ScheduleAmendment (ScheduleAmendment), - runSql) import Server.Util (Service) import Text.Blaze.Html (ToMarkup (..)) -import Text.Blaze.Internal (MarkupM(Empty)) +import Text.Blaze.Internal (MarkupM (Empty)) import Text.ProtocolBuffers (Default (defaultValue)) import Text.Read (readMaybe) import Text.Shakespeare.Text @@ -54,12 +50,12 @@ import Yesod import Yesod.Form import GTFS +import Persist data ControlRoom = ControlRoom - { getBaseurl :: Text - , getGtfs :: GTFS - , getPool :: Pool SqlBackend + { getGtfs :: GTFS + , getPool :: Pool SqlBackend } mkMessage "ControlRoom" "messages" "en" @@ -70,17 +66,16 @@ mkYesod "ControlRoom" [parseRoutes| /train/id/#TripID/#Day TrainViewR GET /train/announce/#TripID/#Day AnnounceR POST /train/del-announce/#UUID DelAnnounceR GET +/token/block/#Token TokenBlock GET /trips TripsViewR GET /trip/#TripID TripViewR GET |] emptyMarkup :: MarkupM a -> Bool emptyMarkup (Empty _) = True -emptyMarkup _ = False +emptyMarkup _ = False instance Yesod ControlRoom where - approot = ApprootMaster (\cr -> getBaseurl cr) - defaultLayout w = do PageContent{..} <- widgetToPageContent w msgs <- getMessages @@ -125,6 +120,9 @@ instance Yesod ControlRoom where input { grid-column: 2; } + .blocked { + background-color: red; + } <body> $forall (status, msg) <- msgs <p class="message #{status}">#{msg} @@ -169,12 +167,28 @@ getTrainViewR trip day = do Nothing -> notFound Just res@Trip{..} -> do anns <- runDB $ selectList [ AnnouncementTrip ==. trip, AnnouncementDay ==. day ] [] + tokens <- runDB $ selectList [ RunningTrip ==. trip, RunningDay ==. day ] [] + lastPing <- runDB $ selectFirst [ TrainPingToken <-. (fmap entityKey tokens) ] [Desc TrainPingTimestamp] defaultLayout $ do mr <- getMessageRender setTitle (toHtml (""+|mr MsgTrip|+" "+|tripTripID|+" "+|mr Msgon|+" "+|day|+"" :: Text)) [whamlet| <h1>_{MsgTrip} <a href="@{TripViewR tripTripID}">#{tripTripID}</a> _{Msgon} <a href="@?{(TrainsR, [("day", T.pack (iso8601Show day))])}">#{day}</a> <section> + <h2>_{MsgLive} + <p><strong>_{MsgLastPing}: </strong> + $maybe Entity _ TrainPing{..} <- lastPing + _{MsgTrainPing trainPingLat trainPingLong trainPingTimestamp} + (<a href="/api/debug/pings/#{trip}/#{day}">_{Msgraw}</a>) + $nothing + <em>(_{MsgNoTrainPing}) + <p><strong>Estimated Delay</strong>: Todo! +<section> + <h2>_{MsgStops} + <ol> + $forall Stop{..} <- tripStops + <li> #{stopArrival} #{stationName stopStation} +<section> <h2>_{MsgAnnouncements} <ul> $forall Entity (AnnouncementKey uuid) Announcement{..} <- anns @@ -186,13 +200,18 @@ getTrainViewR trip day = do ^{widget} <button>Submit <section> - <h2>_{MsgStops} - <ol> - $forall Stop{..} <- tripStops - <li> #{stopArrival} #{stationName stopStation} -<section> - <h2>Vehicle Position - <div> Todo! + <h2>_{MsgTokens} + <table> + <tr><th style="width: 20%">_{MsgAgent}</th><th style="width: 50%">_{MsgToken}</th><th>_{MsgExpires}</th><th>_{MsgStatus}</th> + $forall Entity (RunningKey key) Running{..} <- tokens + <tr :runningBlocked:.blocked> + <td title="#{runningAgent}">#{runningAgent} + <td title="#{key}">#{key} + <td title="#{runningExpires}">#{runningExpires} + $if runningBlocked + <td title="_{MsgUnblockToken}"><a href="@?{(TokenBlock key, [("unblock", "true")])}">_{MsgUnblockToken}</a> + $else + <td title="_{MsgBlockToken}"><a href="@{TokenBlock key}">_{MsgBlockToken}</a> |] @@ -255,6 +274,19 @@ getDelAnnounceR uuid = do Just Announcement{..} -> redirect (TrainViewR announcementTrip announcementDay) +getTokenBlock :: Token -> Handler Html +getTokenBlock token = do + YesodRequest{..} <- getRequest + let blocked = lookup "unblock" reqGetParams /= Just "true" + maybe <- runDB $ do + update (RunningKey token) [ RunningBlocked =. blocked ] + get (RunningKey token) + case maybe of + Just r@Running{..} -> do + liftIO $ print r + redirect (TrainViewR runningTrip runningDay) + Nothing -> notFound + announceForm :: Day -> TripID -> Html -> MForm Handler (FormResult Announcement, Widget) announceForm day tripId = renderDivs $ Announcement @@ -274,3 +306,18 @@ instance ToMarkup Time where instance ToMarkup Day where toMarkup day = toMarkup (iso8601Show day) + +instance ToMessage UTCTime where + toMessage = formatW3 + +instance ToMessage Token where + toMessage (Token uuid) = UUID.toText uuid + +instance ToMarkup UTCTime where + toMarkup = toMarkup . formatW3 + +instance ToMarkup Token where + toMarkup (Token uuid) = toMarkup (UUID.toText uuid) + +instance ToMessage Double where + toMessage = T.pack . show diff --git a/lib/Server/GTFS_RT.hs b/lib/Server/GTFS_RT.hs index d771736..dfdd1eb 100644 --- a/lib/Server/GTFS_RT.hs +++ b/lib/Server/GTFS_RT.hs @@ -51,8 +51,8 @@ import GTFS.Realtime.VehiclePosition as VP (VehiclePositi import Persist (Announcement (..), EntityField (..), Key (..), - RunningTrip (..), - TripPing (..), + Running (..), + TrainPing (..), runSql) import Servant.API ((:<|>) (..)) import Text.ProtocolBuffers (Utf8 (Utf8), @@ -115,15 +115,15 @@ gtfsRealtimeServer gtfs dbpool = handleServiceAlerts :<|> handleTripUpdates :<|> -- TODO: how to propagate delay values to next stops? pure undefined handleVehiclePositions = runSql dbpool $ do - (running :: [Entity RunningTrip]) <- selectList [] [] + (running :: [Entity Running]) <- selectList [] [] pings <- forM running $ \(Entity key entity) -> do - selectFirst [TripPingToken ==. key] [] <&> fmap (, entity) + selectFirst [TrainPingToken ==. key] [] <&> fmap (, entity) dFeedMessage $ Seq.fromList $ mkPosition <$> catMaybes pings - where mkPosition (Entity (TripPingKey key) TripPing{..}, RunningTrip{..}) = + where mkPosition (Entity (TrainPingKey key) TrainPing{..}, Running{..}) = (dFeedEntity (toUtf8 . T.pack . show $ key)) { FE.vehicle = Just $ VehiclePosition - { trip = Just (dTripDescriptor runningTripTripNumber Nothing) - , VP.vehicle = case runningTripVehicle of + { trip = Just (dTripDescriptor runningTrip Nothing) + , VP.vehicle = case runningVehicle of Nothing -> Nothing Just trainset -> Just $ VehicleDescriptor { VD.id = Nothing @@ -132,8 +132,8 @@ gtfsRealtimeServer gtfs dbpool = handleServiceAlerts :<|> handleTripUpdates :<|> , VD.ext'field = defaultValue } , position = Just $ Position - { latitude = double2Float tripPingLat - , longitude = double2Float tripPingLong + { latitude = double2Float trainPingLat + , longitude = double2Float trainPingLong , odometer = Nothing , speed = Nothing , bearing = Nothing @@ -143,7 +143,7 @@ gtfsRealtimeServer gtfs dbpool = handleServiceAlerts :<|> handleTripUpdates :<|> , current_stop_sequence = Nothing , stop_id = Nothing , current_status = Nothing - , timestamp = Just (toStupidTime tripPingTimestamp) + , timestamp = Just (toStupidTime trainPingTimestamp) , congestion_level = Nothing , occupancy_status = Nothing , occupancy_percentage = Nothing diff --git a/lib/Server/Util.hs b/lib/Server/Util.hs index a7a358e..5bfba52 100644 --- a/lib/Server/Util.hs +++ b/lib/Server/Util.hs @@ -1,15 +1,21 @@ {-# LANGUAGE FlexibleContexts #-} -- | mostly the monad the service runs in -module Server.Util (Service, ServiceM, runService) where +module Server.Util (Service, ServiceM, runService, sendErrorMsg) where import Control.Monad.Logger (LoggingT, runStderrLoggingT) +import qualified Data.Aeson as A import Data.ByteString (ByteString) -import Servant (Handler, ServerError, ServerT, err302, - errHeaders, throwError) +import Data.Text (Text) +import Servant (Handler, ServerError, ServerT, err404, + errBody, errHeaders, throwError) type ServiceM = LoggingT Handler type Service api = ServerT api ServiceM runService :: ServiceM a -> Handler a runService = runStderrLoggingT + +sendErrorMsg :: Text -> ServiceM a +sendErrorMsg msg = throwError err404 + { errBody = A.encode $ A.object ["error" A..= (404 :: Int), "msg" A..= msg] } |