{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Main where
import Control.Concurrent.STM
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LB
import Data.Char
import Data.Csv hiding (lookup)
import Data.Either
import Data.Function (on, (&))
import Data.Functor ((<&>))
import Data.FuzzySet.Simple
import Data.List hiding (find)
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import qualified Data.Text.Read as T
import Data.Time.Clock
import Data.Vector (Vector)
import qualified Data.Vector as V
import GHC.Base (Alternative ((<|>)))
import qualified Network.HTTP.Client as Client
import qualified Network.HTTP.Client.Rustls as Client
import Network.HTTP.Types
import Network.Wai
import Network.Wai.Handler.Warp (run)
import Network.Wai.Middleware.RequestLogger
import Util
data Platform = Platform
{ osmType :: Text
, osmId :: Text
, ref :: Maybe Text
, localRef :: Maybe Text
, osmLevel :: Maybe Text
, osmPlatform :: Maybe Text
, osmSection :: Maybe Text
, osmPlatformEdge :: Maybe Text
} deriving Show
instance FromRecord Platform where
parseRecord v =
Platform <$>
v .! 0 <*>
v .! 1 <*>
v .! 2 <*>
v .! 3 <*>
(v .! 4 <|> v .! 5) <*>
v .! 6 <*>
v .! 7 <*>
v .! 8
data Answer
= Redirect Text
| Plaintext Text
| Html Text
| Notfound
| Unimplemented
maybeAnswer :: (a -> Answer) -> Maybe a -> Answer
maybeAnswer = maybe Notfound
data AppData = AppData
{ ril100map :: DoubleMap Ril100 Text
, leitpunktMap :: DoubleMap Ril100 Text
, ril100set :: FuzzySet
, ril100BaseUrl :: Text
, leitpunktBaseUrl :: Text
, clientManager :: Client.Manager
, platformCache :: TVar (Map Ril100 (UTCTime, Answer))
, cacheTime :: NominalDiffTime
}
app :: AppData -> Application
app AppData{..} request respond = mkAnswer >>= (respond . toResponse)
where
mkAnswer :: IO Answer
mkAnswer = case filter (/= mempty) (pathInfo request) of
[] -> pure helptext
["favicon.ico"] -> pure Notfound
["cache"] -> do
cache <- readTVarIO platformCache
now <- getCurrentTime
M.toList cache
& fmap (\(ril100, (age, _)) -> (T.pack . show) (unRil100 ril100, now `diffUTCTime` age))
& T.unlines
& (pure . Plaintext)
[query]
| not (T.any isLower query) && host `elem` ["leitpunkt"]
-> lookupName query leitpunktMap
>>= (`lookupCode` ril100map)
& maybeAnswer Plaintext & pure
| not (T.any isLower query)
-> lookupCode (Ril100 query) ril100map
& maybeAnswer Plaintext & pure
| host `elem` ["leitpunkt"]
-> pure $ case findStationName query ril100set of
None -> Notfound
Exact (_,match) -> lookupName match ril100map
>>= (`lookupCode` leitpunktMap)
& maybeAnswer Plaintext
Fuzzy (_,match) -> Redirect (leitpunktBaseUrl <> "/" <> match)
| otherwise
-> pure $ case findStationName query ril100set of
None -> Notfound
Exact (_,match) -> lookupName match ril100map
& maybeAnswer (Plaintext . unRil100)
Fuzzy (_,match) -> Redirect (ril100BaseUrl <> "/" <> match)
[query, segment] | segment `elem` ["gleis", "track", "tracks", "gleise", "platform", "platforms", "fetch"]
-> case queriedRil100 query of
None -> pure Notfound
Fuzzy url -> pure (Redirect (T.intercalate "/" [url, segment]))
Exact ril100 -> do
maybeCache <- readTVarIO platformCache <&> M.lookup ril100
now <- getCurrentTime
case maybeCache of
Just (age, answer)
| now `diffUTCTime` age < cacheTime && segment /= "fetch" -> pure answer
_ -> do
let overpassQuery = " \
\[out:csv(::type, ::id, ref, local_ref, level, layer, platform, section, track;false)][timeout:25];\n\
\nwr[~\"railway:ref|railway:ref:parent\"~\"^"<>encodeUtf8 (unRil100 ril100)<>"$\"][operator~\"^(DB|Deutsch)\"];\n\
\(._;rel[public_transport~\"stop_area|stop_area_group\"](bn);) -> .a;\n\
\rel[public_transport~\"stop_area|stop_area_group\"](br.a) -> .b;\n\
\(.a;.b;);\n\
\nwr[railway=platform](>>);\n\
\foreach {\n\
\ ._ -> .a;\n\
\ out tags;\n\
\ >> -> .p;\n\
\ nwr.p[\"railway\"=\"platform_edge\"][\"ref\"] -> .edges;\n\
\ if (edges.count(nwr) == 0) {\n\
\ >>;\n\
\ node._[\"railway:platform:section\"] -> ._;\n\
\ convert node platform = a.u(id()),\n\
\ section = t[\"railway:platform:section\"],\n\
\ ::id = id();\n\
\ out tags;\n\
\ } else { \n\
\ foreach.edges {\n\
\ ._ -> .b;\n\
\ >>;\n\
\ node._[\"railway:platform:section\"] -> ._;\n\
\ convert node platform = a.u(id()),\n\
\ section = t[\"railway:platform:section\"],\n\
\ track = b.u(t[\"ref\"]),\n\
\ ::id = id();\n\
\ out tags;\n\
\ }\n\
\ }\n\
\}\n"
let req = "https://overpass-api.de/api/interpreter"
{ Client.requestBody = Client.RequestBodyBS overpassQuery
, Client.method = "POST"}
putStrLn $ "looking up platforms for " <> show ril100
response <- Client.httpLbs req clientManager
case decodeWith tsvOptions NoHeader (Client.responseBody response) of
Left _ -> pure Notfound
Right (platforms :: Vector Platform)
| null platforms -> pure $ Html $
"Found no information, sorry.
If you want to investigate, the attempted query was:
"
<> decodeUtf8 overpassQuery
<> ""
| otherwise -> do
let answer = V.toList platforms
& sortOn (maybe (0::Int) (fromRight 0 . fmap fst . T.signed T.decimal) . osmLevel)
<&> renderPlatform platforms
& (Html . T.concat)
atomically $ do
cache <- readTVar platformCache
writeTVar platformCache (M.insert ril100 (now, answer) cache)
pure answer
where
getRef (Just ref) _ = Just ref
getRef Nothing (Just ref) = Just ref
getRef _ _ = Nothing
renderPlatform others p = case getRef (ref p) (localRef p) of
Just ref -> mkAnchor p ref<>""<>renderedSections<>"