aboutsummaryrefslogtreecommitdiff
path: root/lib/Server
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--lib/Server.hs4
-rw-r--r--lib/Server/Util.hs20
2 files changed, 18 insertions, 6 deletions
diff --git a/lib/Server.hs b/lib/Server.hs
index 15027b3..3fc2c5a 100644
--- a/lib/Server.hs
+++ b/lib/Server.hs
@@ -36,7 +36,6 @@ import Prometheus (Info (Info), exportMetricsAsText,
gauge, register)
import Prometheus.Metric.GHC (ghcMetrics)
import Servant (Application, err401, serve,
- serveDirectoryFileServer,
throwError)
import Servant.API ((:<|>) (..))
import Servant.Server (hoistServer)
@@ -47,7 +46,8 @@ import Server.GTFS_RT (gtfsRealtimeServer)
import Server.Ingest (handleTrackerRegister,
handleTrainPing, handleWS)
import Server.Subscribe (handleSubscribe)
-import Server.Util (Service, runLogging, runService)
+import Server.Util (Service, runLogging, runService,
+ serveDirectoryFileServer)
import System.IO.Unsafe (unsafePerformIO)
import Yesod (toWaiAppPlain)
diff --git a/lib/Server/Util.hs b/lib/Server/Util.hs
index 290b9c5..b519a86 100644
--- a/lib/Server/Util.hs
+++ b/lib/Server/Util.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE RecordWildCards #-}
-- | mostly the monad the service runs in
-module Server.Util (Service, ServiceM, runService, sendErrorMsg, secondsNow, utcToSeconds, runLogging, getTzseries) where
+module Server.Util (Service, ServiceM, runService, sendErrorMsg, secondsNow, utcToSeconds, runLogging, getTzseries, serveDirectoryFileServer) where
import Config (LoggingConfig (..),
ServerConfig (..))
@@ -27,14 +27,18 @@ import Data.Time (Day, UTCTime (..),
import Data.Time.LocalTime.TimeZone.Olson (getTimeZoneSeriesFromOlsonFile)
import Data.Time.LocalTime.TimeZone.Series (TimeZoneSeries)
import Fmt ((+|), (|+))
+import GHC.IO (unsafePerformIO)
import GHC.IO.Exception (IOException (IOError))
import GTFS (Seconds (..))
import Prometheus (MonadMonitor (doIO))
+import qualified Servant
import Servant (Handler, ServerError,
ServerT, err404, errBody,
errHeaders, throwError)
-import System.FilePath ((</>))
import System.IO (stderr)
+import System.OsPath (OsPath, decodeFS,
+ decodeUtf, encodeUtf,
+ (</>))
import System.Process.Extra (callProcess)
type ServiceM = LoggingT (ReaderT LoggingConfig Handler)
@@ -87,5 +91,13 @@ utcToSeconds time day =
Seconds $ round $ nominalDiffTimeToSeconds $ diffUTCTime time (UTCTime day 0)
getTzseries :: ServerConfig -> Text -> IO TimeZoneSeries
-getTzseries settings tzname = getTimeZoneSeriesFromOlsonFile
- (serverConfigZoneinfoPath settings </> T.unpack tzname)
+getTzseries settings tzname = do
+ suffix <- encodeUtf (T.unpack tzname)
+ -- TODO: submit a patch to timezone-olson making it accept OsPath
+ legacyPath <- decodeFS (serverConfigZoneinfoPath settings </> suffix)
+ getTimeZoneSeriesFromOlsonFile legacyPath
+
+-- TODO: patch servant / wai to use OsPath?
+serveDirectoryFileServer :: OsPath -> ServerT Servant.Raw m
+serveDirectoryFileServer =
+ Servant.serveDirectoryFileServer . unsafePerformIO . decodeUtf