{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE ExplicitNamespaces #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TypeApplications #-} -- Implementation of the API. This module is the main point of the program. module Server (application) where import Conduit (MonadTrans (lift), ResourceT) import Control.Concurrent.STM import Control.Monad (when) import Control.Monad.Extra (whenM) import Control.Monad.IO.Class (MonadIO (liftIO)) import Control.Monad.Logger.CallStack (NoLoggingT) import Control.Monad.Reader (forM) import Control.Monad.Trans.Maybe (MaybeT (..)) import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON), ToJSONKey, genericParseJSON, genericToJSON) import qualified Data.Aeson as A import Data.Coerce (coerce) import Data.Functor ((<&>)) import Data.Map (Map) import qualified Data.Map as M import Data.Pool (Pool) import Data.Proxy (Proxy (Proxy)) import Data.Swagger hiding (get) import Data.Text (Text) import Data.Time (NominalDiffTime, UTCTime (utctDay), addUTCTime, dayOfWeek, diffUTCTime, getCurrentTime, nominalDay) import Data.UUID (UUID) import qualified Data.UUID as UUID import qualified Data.UUID.V4 as UUID import Data.Vector (Vector) import Database.Persist import Database.Persist.Postgresql import GHC.Generics (Generic) import GTFS import Servant (Application, FromHttpApiData (parseUrlPiece), Server, err401, err404, serve, throwError) import Servant.API (Capture, FromHttpApiData, Get, JSON, Post, ReqBody, type (:<|>) ((:<|>))) import Servant.Docs (DocCapture (..), DocQueryParam (..), ParamKind (..), ToCapture (..), ToParam (..)) import Servant.Server (Handler) import Servant.Swagger (toSwagger) import Web.PathPieces (PathPiece) import API import Persist application :: GTFS -> Pool SqlBackend -> IO Application application gtfs dbpool = do doMigration dbpool pure $ serve (Proxy @CompleteAPI) $ server gtfs dbpool -- databaseMigration :: ConnectionString -> IO () doMigration pool = runSql pool $ -- TODO: before that, check if the uuid module is enabled -- in sql: check if SELECT * FROM pg_extension WHERE extname = 'uuid-ossp'; -- returns an empty list runMigration migrateAll server :: GTFS -> Pool SqlBackend -> Server CompleteAPI server gtfs@GTFS{..} dbpool = handleDebugAPI :<|> handleStations :<|> handleTimetable :<|> handleTrip :<|> handleRegister :<|> handleTripPing :<|> handleDebugState where handleStations = pure stations handleTimetable station = do -- TODO: resolve "overlay" trips (perhaps just additional CalendarDates?) today <- liftIO getCurrentTime <&> utctDay pure $ tripsOnDay gtfs today handleTrip trip = case M.lookup trip trips of Just res -> pure res Nothing -> throwError err404 handleRegister tripID = do expires <- liftIO $ getCurrentTime <&> addUTCTime validityPeriod RunningTripKey token <- runSql dbpool $ insert (RunningTrip expires False tripID) pure token handleTripPing ping = do checkTokenValid dbpool (coerce $ tripPingToken ping) -- TODO: are these always inserted in order? runSql dbpool $ insert ping pure () 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] [] pure (uuid, fmap entityVal entities) pure (M.fromList pairs) handleDebugAPI = pure $ toSwagger (Proxy @API) -- 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) $ throwError err401 whenM (hasExpired (runningTripExpires trip)) $ throwError err401 where try m = m >>= \case Just a -> pure a Nothing -> throwError err404 hasExpired :: MonadIO m => UTCTime -> m Bool hasExpired limit = do now <- liftIO getCurrentTime pure (now > limit) validityPeriod :: NominalDiffTime validityPeriod = nominalDay