aboutsummaryrefslogtreecommitdiff
path: root/lib/API.hs
blob: dc348d345932ce5a2bf3e309eb5ad4e20d1f66dc (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
{-# LANGUAGE DataKinds     #-}
{-# LANGUAGE TypeOperators #-}

-- | The sole authorative definition of this server's API, given as a Servant-style
-- Haskell type. All other descriptions of the API are generated from this one.
module API (API, CompleteAPI) 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 (:<|>) ((:<|>)))

-- | The server's API (as it is actually intended).
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])

-- | The server's API with an additional debug route for accessing the specification
-- itself. Split from API to prevent the API documenting the format in which it is
-- documented, which would be silly and way to verbose.
type CompleteAPI = "debug" :> "openapi" :> Get '[JSON] Swagger
  :<|> API

{-
TODO:
there should be a basic API allowing the questions:
 - what are the next trips leaving from $station? (or $geolocation?)
 - all stops of a given tripID

then the "ingress" API:
 - train ping (location, estimated delay, etc.)
 - cancel trip
 - add trip?

-}