aboutsummaryrefslogtreecommitdiff
path: root/lib/API.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/API.hs')
-rw-r--r--lib/API.hs34
1 files changed, 23 insertions, 11 deletions
diff --git a/lib/API.hs b/lib/API.hs
index 3fb4c3c..dc348d3 100644
--- a/lib/API.hs
+++ b/lib/API.hs
@@ -1,15 +1,9 @@
-{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DerivingStrategies #-}
-{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE GADTs #-}
-{-# LANGUAGE MultiParamTypeClasses #-}
-{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeOperators #-}
-{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeOperators #-}
-
-module API where
+-- | 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)
@@ -21,6 +15,7 @@ import Servant (Application, FromHttpApiData (parseUrlPiece),
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)
@@ -31,5 +26,22 @@ type API = "stations" :> Get '[JSON] (Map StationID Station)
:<|> "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?
+
+-}