From 1e04f049b101d8250b8964dd0b465e703d03a4c2 Mon Sep 17 00:00:00 2001
From: stuebinm
Date: Fri, 10 May 2024 17:13:53 +0200
Subject: space time diagrams: real time & time zones
---
CHANGELOG.md | 1 +
lib/Server/Frontend.hs | 2 +-
lib/Server/Frontend/SpaceTime.hs | 197 ++++++++++++++++++++++++++++-----------
lib/Server/Frontend/Tickets.hs | 65 +++++++------
4 files changed, 179 insertions(+), 86 deletions(-)
diff --git a/CHANGELOG.md b/CHANGELOG.md
index 85a3dcb..68dc1d2 100644
--- a/CHANGELOG.md
+++ b/CHANGELOG.md
@@ -8,6 +8,7 @@
* Restructure: the backend server is no responsible for keeping track of which
trip on OBU is on, further minimising the required onboard-side logic
* Logs can now be sent as push notifications via ntfy-sh
+* added Space-Time diagrams. These will not work correctly if stops are in different time zones
## 0.0.1.0 -- ~ 2022-11-01
diff --git a/lib/Server/Frontend.hs b/lib/Server/Frontend.hs
index 3beb9e0..cec4fa7 100644
--- a/lib/Server/Frontend.hs
+++ b/lib/Server/Frontend.hs
@@ -5,8 +5,8 @@ module Server.Frontend (Frontend(..), Handler) where
import Server.Frontend.Gtfs
import Server.Frontend.OnboardUnit
import Server.Frontend.Routes
-import Server.Frontend.Tickets
import Server.Frontend.SpaceTime
+import Server.Frontend.Tickets
import Yesod
import Yesod.Auth
diff --git a/lib/Server/Frontend/SpaceTime.hs b/lib/Server/Frontend/SpaceTime.hs
index 307e795..878a627 100644
--- a/lib/Server/Frontend/SpaceTime.hs
+++ b/lib/Server/Frontend/SpaceTime.hs
@@ -1,104 +1,189 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
-module Server.Frontend.SpaceTime (getSpaceTimeDiagramR) where
+module Server.Frontend.SpaceTime (getSpaceTimeDiagramR, mkSpaceTimeDiagram, mkSpaceTimeDiagramHandler) where
-import Server.Frontend.Routes
+import Server.Frontend.Routes
+import Control.Monad (forM, when)
+import Data.Coerce (coerce)
+import Data.Function (on, (&))
import Data.Functor ((<&>))
+import Data.Graph (path)
+import Data.List
import qualified Data.Map as M
+import Data.Maybe (catMaybes, mapMaybe)
import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time (Day, UTCTime (..), getCurrentTime)
import qualified Data.Vector as V
+import Debug.Trace (trace)
+import Fmt ((+|), (|+))
+import GHC.Float (double2Int, int2Double)
+import GTFS (Seconds (unSeconds))
import qualified GTFS
+import Persist
+import Server.Util (getTzseries)
import Text.Blaze.Html (Html)
-import qualified Data.Text as T
+import Text.Read (readMaybe)
import Yesod
-import Text.Read (readMaybe)
-import Data.Time (getCurrentTime, UTCTime (..))
-import Persist
-import Data.Function ((&), on)
-import Data.List
-import Data.Coerce (coerce)
-import Control.Monad (when, forM)
-import GHC.Float (int2Double)
-import Fmt ((|+), (+|))
-import Data.Maybe (catMaybes, mapMaybe)
-import GTFS (Seconds(unSeconds))
getSpaceTimeDiagramR :: Handler Html
getSpaceTimeDiagramR = do
-
req <- getRequest
-
day <- case lookup "day" (reqGetParams req) >>= (readMaybe . T.unpack) of
- Just day -> pure day
+ Just day -> pure day
Nothing -> liftIO $ getCurrentTime <&> utctDay
- tickets <- runDB $ selectList [ TicketDay ==. day ] [] >>= mapM (\ticket -> do
- stops <- selectList [StopTicket ==. entityKey ticket] []
- pure (ticket, stops))
-
-
- -- TODO: this should be a nicer error message
- when (null tickets)
- notFound
+ mkSpaceTimeDiagramHandler day >>= \case
+ Nothing -> notFound
+ Just widget -> defaultLayout [whamlet|
+
_{MsgSpaceTimeDiagram}
+
+ ^{widget}
+ |]
+mkSpaceTimeDiagramHandler :: Day -> Handler (Maybe Widget)
+mkSpaceTimeDiagramHandler day = do
+ tickets <- runDB $ selectList [ TicketDay ==. day ] [] >>= mapM (\ticket -> do
+ stops <- selectList [StopTicket ==. entityKey ticket] [] >>= mapM (\(Entity _ stop@Stop{..}) -> do
+ arrival <- lift $ timeToPos day stopArrival
+ departure <- lift $ timeToPos day stopDeparture
+ pure (stop, arrival, departure))
+ anchors <- selectList [TrainAnchorTicket ==. entityKey ticket] [Desc TrainAnchorSequence]
+ pure (ticket, stops, anchors))
+
+ case tickets of
+ [] ->
+ pure Nothing
+ _ ->
+ mkSpaceTimeDiagram day tickets
+ <&> Just
+
+-- | Safety: tickets may not be empty
+mkSpaceTimeDiagram
+ :: Day
+ -> [(a, [(Stop, Double, Double)], [Entity TrainAnchor])]
+ -> Handler Widget
+mkSpaceTimeDiagram day tickets = do
-- we take the longest trip of the day. This will lead to unreasonable results
-- if there's more than one shape (this whole route should probably take a shape id tbh)
- stations <- runDB $ fmap snd tickets
- & maximumBy (compare `on` length)
- & fmap entityVal
- & sortOn stopSequence
- & mapM (\stop -> do
- s <- getJust (stopStation stop)
- pure (stopStation stop, s, stop))
+ stations <- runDB $ fmap (\(_,stops,_) -> stops) tickets
+ & maximumBy (compare `on` length)
+ & fmap (\(stop, _, _) -> stop)
+ & sortOn stopSequence
+ & zip [0..]
+ & mapM (\(idx, stop) -> do
+ s <- getJust (stopStation stop)
+ pure (stopStation stop, s, stop { stopSequence = idx }))
let maxSequence = stopSequence ((\(_,_,stop) -> stop) (last stations))
- let scaleSequence a = int2Double a * 100 / int2Double maxSequence
+ let scaleSequence a = a * 100 / int2Double maxSequence
- let (minY, maxY) = tickets
- <&> snd
+
+ (minY, maxY) <- tickets
+ <&> (\(_,stops,_) -> stops)
& concat
- <&> (timeToPos . stopDeparture . entityVal)
- & (\ys -> (minimum ys - 20, maximum ys + 20))
+ & mapM (timeToPos day . stopDeparture . (\(stop, _, _) -> stop))
+ <&> (\ys -> (minimum ys - 10, maximum ys + 30))
+
+ let timezone = head stations
+ & (\(_,_,stop) -> stop)
+ & stopArrival
+ & GTFS.tzname
- defaultLayout $ do
- [whamlet|
- _{MsgSpaceTimeDiagram}
+ timeLines <- ([0,3600..(24*3600)]
+ & mapM ((\a -> timeToPos day a <&> (,a)) . \seconds -> GTFS.Time seconds timezone))
+ <&> takeWhile ((< maxY - 20) . fst) . filter ((> minY) . fst)
-