{-# LANGUAGE DataKinds #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module API where import Data.Map (Map) import Data.Swagger (Swagger) import GTFS import Persist import Servant (Application, FromHttpApiData (parseUrlPiece), Server, err401, err404, serve, throwError, type (:>)) import Servant.API (Capture, FromHttpApiData, Get, JSON, Post, ReqBody, type (:<|>) ((:<|>))) type API = "stations" :> Get '[JSON] (Map StationID Station) :<|> "timetable" :> Capture "Station ID" StationID :> Get '[JSON] (Map TripID (Trip Deep)) :<|> "trip" :> Capture "Trip ID" TripID :> Get '[JSON] (Trip Deep) -- ingress API (put this behind BasicAuth?) -- TODO: perhaps require a first ping for registration? :<|> "trip" :> "register" :> Capture "Trip ID" TripID :> Post '[JSON] Token -- TODO: perhaps a websocket instead? :<|> "trip" :> "ping" :> ReqBody '[JSON] TripPing :> Post '[JSON] () -- debug things :<|> "debug" :> "state" :> Get '[JSON] (Map Token [TripPing]) type CompleteAPI = "debug" :> "openapi" :> Get '[JSON] Swagger :<|> API