{-# LANGUAGE DataKinds #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PartialTypeSignatures #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TupleSections #-} module Server.GTFS_RT (gtfsRealtimeServer) where import API (GtfsRealtimeAPI) import Control.Lens ((&), (.~)) import Control.Monad (forM) import Control.Monad.Extra (mapMaybeM) import Control.Monad.IO.Class (MonadIO (..)) import Data.Coerce (coerce) import Data.Functor ((<&>)) import Data.List.NonEmpty (NonEmpty, nonEmpty) import qualified Data.Map as M import Data.Maybe (catMaybes, fromMaybe, mapMaybe) import Data.Pool (Pool) import Data.ProtoLens (defMessage) import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar (Day, toGregorian) import Data.Time.Clock (UTCTime (utctDay), addUTCTime, diffUTCTime, getCurrentTime) import Data.Time.Clock.System (SystemTime (systemSeconds), getSystemTime, utcToSystemTime) import Data.Time.Format.ISO8601 (iso8601Show) import Data.UUID (toASCIIBytes, toLazyASCIIBytes) import qualified Data.UUID as UUID import qualified Data.Vector as V import Database.Persist (Entity (..), PersistQueryRead (selectFirst), SelectOpt (Asc, Desc), get, getJust, selectKeysList, selectList, (<-.), (==.)) import Database.Persist.Postgresql (SqlBackend) import Extrapolation (Extrapolator (extrapolateAtPosition, extrapolateAtSeconds), LinearExtrapolator (..)) import GHC.Float (double2Float, int2Double) import GTFS (Depth (..), GTFS (..), Seconds (..), Trip (..), TripId, showTimeWithSeconds, stationId, toSeconds, toUTC, tripsOnDay) import Persist (Announcement (..), EntityField (..), Key (..), Station (..), Stop (..), Ticket (..), Token (..), Tracker (..), TrainAnchor (..), TrainPing (..), latitude, longitude, runSql) import qualified Proto.GtfsRealtime as RT import qualified Proto.GtfsRealtime_Fields as RT import Servant.API ((:<|>) (..)) import Server.Util (Service, secondsNow) -- | formats a day in the "stupid" format used by gtfs realtime toStupidDate :: Day -> Text toStupidDate date = pad 4 year <> pad 2 month <> pad 2 day where (year, month, day) = toGregorian date pad len num = T.pack $ if ndigits < len then replicate (len - ndigits) '0' <> show num else show num where ndigits = length (show num) -- | basically unix timestamps, raw (because why not i guess) toStupidTime :: Num i => UTCTime -> i toStupidTime = fromIntegral . systemSeconds . utcToSystemTime gtfsRealtimeServer :: GTFS -> Pool SqlBackend -> Service GtfsRealtimeAPI gtfsRealtimeServer gtfs@GTFS{..} dbpool = handleServiceAlerts :<|> handleTripUpdates :<|> handleVehiclePositions where handleServiceAlerts = runSql dbpool $ do announcements <- selectList [] [] alerts <- forM announcements $ \(Entity (AnnouncementKey uuid) announcement@Announcement{..}) -> do ticket <- getJust announcementTicket pure $ mkAlert uuid announcement ticket defFeedMessage alerts where mkAlert :: UUID.UUID -> Announcement -> Ticket -> RT.FeedEntity mkAlert uuid Announcement{..} Ticket{..} = defMessage & RT.id .~ UUID.toText uuid & RT.alert .~ (defMessage & RT.activePeriod .~ [ defMessage :: RT.TimeRange ] & RT.informedEntity .~ [ defMessage & RT.trip .~ defTripDescriptor ticketTripName (Just ticketDay) Nothing ] & RT.maybe'url .~ fmap (monolingual "de") announcementUrl & RT.headerText .~ monolingual "de" announcementHeader & RT.descriptionText .~ monolingual "de" announcementMessage ) handleTripUpdates = runSql dbpool $ do now <- liftIO getCurrentTime let today = utctDay now nowSeconds <- secondsNow today -- let running = M.toList (tripsOnDay gtfs today) tickets <- selectList [TicketCompleted ==. False, TicketDay ==. today] [Asc TicketTripName] tripUpdates <- forM tickets $ \(Entity key Ticket{..}) -> do selectList [TrainAnchorTicket ==. key] [] >>= \a -> case nonEmpty a of Nothing -> pure Nothing Just anchors -> do stops <- selectList [StopTicket ==. key] [Asc StopArrival] >>= mapM (\(Entity _ stop) -> do station <- getJust (stopStation stop) pure (stop, station)) let anchorEntities = fmap entityVal anchors let lastCall = extrapolateAtSeconds LinearExtrapolator anchorEntities nowSeconds let atStations = flip fmap stops $ \(stop, station) -> (, stop, station) <$> extrapolateAtPosition LinearExtrapolator anchorEntities (int2Double (stopSequence stop)) let (lastAnchor, lastStop, lastStation) = last (catMaybes atStations) -- google's TripUpdateTooOld does not like information on trips which have ended let stillRunning = trainAnchorDelay lastAnchor + toSeconds (stopArrival lastStop) tzseries today > nowSeconds + 5 * 60 -- google's TripUpdateTooOld check fails if the given timestamp is older than ~ half an hour let isOutdated = maybe False (\a -> trainAnchorCreated a `diffUTCTime` now < 20 * 60) lastCall pure $ if not stillRunning && not isOutdated then Nothing else Just $ defMessage & RT.id .~ UUID.toText (coerce key) & RT.tripUpdate .~ (defMessage & RT.trip .~ defTripDescriptor ticketTripName (Just today) (Just $ T.pack (showTimeWithSeconds $ stopDeparture $ fst $ head stops)) & RT.stopTimeUpdate .~ fmap mkStopTimeUpdate (catMaybes atStations) & RT.maybe'delay .~ Nothing -- lastCall <&> (fromIntegral . unSeconds . trainAnchorDelay) & RT.maybe'timestamp .~ fmap (toStupidTime . trainAnchorCreated) lastCall ) where mkStopTimeUpdate :: (TrainAnchor, Stop, Station) -> RT.TripUpdate'StopTimeUpdate mkStopTimeUpdate (TrainAnchor{..}, Stop{..}, Station{..}) = defMessage & RT.stopSequence .~ fromIntegral stopSequence & RT.stopId .~ stationShortName & RT.arrival .~ (defMessage & RT.delay .~ fromIntegral (unSeconds trainAnchorDelay) & RT.time .~ toStupidTime (addUTCTime (fromIntegral $ unSeconds trainAnchorDelay) (toUTC stopArrival tzseries today)) & RT.uncertainty .~ 60 ) & RT.departure .~ (defMessage & RT.delay .~ fromIntegral (unSeconds trainAnchorDelay) & RT.time .~ toStupidTime (addUTCTime (fromIntegral $ unSeconds trainAnchorDelay) (toUTC stopDeparture tzseries today)) & RT.uncertainty .~ 60 ) & RT.scheduleRelationship .~ RT.TripUpdate'StopTimeUpdate'SCHEDULED defFeedMessage (catMaybes tripUpdates) handleVehiclePositions = runSql dbpool $ do ticket <- selectList [TicketCompleted ==. False] [] -- TODO: reimplement this (since trainpings no longer reference tickets it's gone for now) -- positions <- forM ticket $ \(Entity key ticket) -> do -- selectFirst [TrainPingTicket ==. key] [Desc TrainPingTimestamp] >>= \case -- Nothing -> pure Nothing -- Just lastPing -> -- pure (Just $ mkPosition (lastPing, ticket)) defFeedMessage [] -- (catMaybes positions) where mkPosition :: (Entity TrainPing, Ticket) -> RT.FeedEntity mkPosition (Entity key TrainPing{..}, Ticket{..}) = defMessage & RT.id .~ T.pack (show key) & RT.vehicle .~ (defMessage & RT.trip .~ defTripDescriptor ticketTripName Nothing Nothing & RT.maybe'vehicle .~ case ticketVehicle of Nothing -> Nothing Just trainset -> Just $ defMessage & RT.label .~ trainset & RT.position .~ (defMessage & RT.latitude .~ double2Float (latitude trainPingGeopos) & RT.longitude .~ double2Float (longitude trainPingGeopos) ) -- TODO: should probably give currentStopSequence/stopId here as well & RT.timestamp .~ toStupidTime trainPingTimestamp ) monolingual :: Text -> Text -> RT.TranslatedString monolingual code msg = defMessage & RT.translation .~ [ defMessage & RT.text .~ msg & RT.language .~ code ] defFeedMessage :: MonadIO m => [RT.FeedEntity] -> m RT.FeedMessage defFeedMessage entities = do now <- liftIO getSystemTime <&> systemSeconds pure $ defMessage & RT.header .~ (defMessage & RT.gtfsRealtimeVersion .~ "2.0" & RT.incrementality .~ RT.FeedHeader'FULL_DATASET & RT.timestamp .~ fromIntegral now ) & RT.entity .~ entities defTripDescriptor :: TripId -> Maybe Day -> Maybe Text -> RT.TripDescriptor defTripDescriptor tripId day starttime = defMessage & RT.tripId .~ tripId & RT.scheduleRelationship .~ RT.TripDescriptor'SCHEDULED & RT.maybe'startTime .~ starttime & RT.maybe'startDate .~ fmap toStupidDate day