aboutsummaryrefslogtreecommitdiff
path: root/lib/Server/Frontend/Gtfs.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Server/Frontend/Gtfs.hs')
-rw-r--r--lib/Server/Frontend/Gtfs.hs57
1 files changed, 57 insertions, 0 deletions
diff --git a/lib/Server/Frontend/Gtfs.hs b/lib/Server/Frontend/Gtfs.hs
new file mode 100644
index 0000000..bc21ab7
--- /dev/null
+++ b/lib/Server/Frontend/Gtfs.hs
@@ -0,0 +1,57 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE QuasiQuotes #-}
+{-# LANGUAGE RecordWildCards #-}
+
+module Server.Frontend.Gtfs (getGtfsTripViewR, getGtfsTripsViewR) where
+
+import Server.Frontend.Routes
+
+import Data.Functor ((<&>))
+import qualified Data.Map as M
+import Data.Text (Text)
+import qualified Data.Vector as V
+import qualified GTFS
+import Text.Blaze.Html (Html)
+import Yesod
+
+getGtfsTripsViewR :: Handler Html
+getGtfsTripsViewR = do
+ GTFS.GTFS{..} <- getYesod <&> getGtfs
+ defaultLayout $ do
+ setTitle "List of Trips"
+ [whamlet|
+<h1>List of Trips
+<section><ul>
+ $forall trip@GTFS.Trip{..} <- trips
+ <li><a href="@{GtfsTripViewR tripTripId}">#{GTFS.tripName trip}</a>
+ : #{GTFS.stopDeparture (V.head tripStops)} #{GTFS.stationName (GTFS.stopStation (V.head tripStops))}
+|]
+
+
+getGtfsTripViewR :: GTFS.TripId -> Handler Html
+getGtfsTripViewR tripId = do
+ GTFS.GTFS{..} <- getYesod <&> getGtfs
+ case M.lookup tripId trips of
+ Nothing -> notFound
+ Just trip@GTFS.Trip{..} -> defaultLayout [whamlet|
+<h1>_{MsgTrip} #{GTFS.tripName trip}
+<section>
+ <h2>_{MsgInfo}
+ <p><strong>_{MsgtripId}:</strong> #{tripTripId}
+ <p><strong>_{MsgtripHeadsign}:</strong> #{mightbe tripHeadsign}
+ <p><strong>_{MsgtripShortname}:</strong> #{mightbe tripShortName}
+<section>
+ <h2>_{MsgStops}
+ <ol>
+ $forall GTFS.Stop{..} <- tripStops
+ <div>(#{stopSequence}) #{stopArrival} #{GTFS.stationName stopStation}
+<section>
+ <h2>Dates
+ <ul>
+ TODO!
+|]
+
+mightbe :: Maybe Text -> Text
+mightbe (Just a) = a
+mightbe Nothing = ""