{-# LANGUAGE CPP #-}
module Servant.Server.StaticFiles
( serveDirectoryWebApp
, serveDirectoryWebAppLookup
, serveDirectoryFileServer
, serveDirectoryEmbedded
, serveDirectoryWith
,
serveDirectory
) where
import Data.ByteString
(ByteString)
import Network.Wai.Application.Static
import Servant.API.Raw
(Raw)
import Servant.Server
(ServerT, Tagged (..))
import System.FilePath
(addTrailingPathSeparator)
import WaiAppStatic.Storage.Filesystem
(ETagLookup)
serveDirectoryWebApp :: FilePath -> ServerT Raw m
serveDirectoryWebApp :: FilePath -> ServerT Raw m
serveDirectoryWebApp = StaticSettings -> Tagged m Application
forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith (StaticSettings -> Tagged m Application)
-> (FilePath -> StaticSettings) -> FilePath -> Tagged m Application
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> StaticSettings
defaultWebAppSettings (FilePath -> StaticSettings)
-> (FilePath -> FilePath) -> FilePath -> StaticSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
fixPath
serveDirectoryFileServer :: FilePath -> ServerT Raw m
serveDirectoryFileServer :: FilePath -> ServerT Raw m
serveDirectoryFileServer = StaticSettings -> Tagged m Application
forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith (StaticSettings -> Tagged m Application)
-> (FilePath -> StaticSettings) -> FilePath -> Tagged m Application
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> StaticSettings
defaultFileServerSettings (FilePath -> StaticSettings)
-> (FilePath -> FilePath) -> FilePath -> StaticSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
fixPath
serveDirectoryWebAppLookup :: ETagLookup -> FilePath -> ServerT Raw m
serveDirectoryWebAppLookup :: ETagLookup -> FilePath -> ServerT Raw m
serveDirectoryWebAppLookup ETagLookup
etag =
StaticSettings -> Tagged m Application
forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith (StaticSettings -> Tagged m Application)
-> (FilePath -> StaticSettings) -> FilePath -> Tagged m Application
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> ETagLookup -> StaticSettings)
-> ETagLookup -> FilePath -> StaticSettings
forall a b c. (a -> b -> c) -> b -> a -> c
flip FilePath -> ETagLookup -> StaticSettings
webAppSettingsWithLookup ETagLookup
etag (FilePath -> StaticSettings)
-> (FilePath -> FilePath) -> FilePath -> StaticSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
fixPath
serveDirectoryEmbedded :: [(FilePath, ByteString)] -> ServerT Raw m
serveDirectoryEmbedded :: [(FilePath, ByteString)] -> ServerT Raw m
serveDirectoryEmbedded [(FilePath, ByteString)]
files = StaticSettings -> ServerT Raw m
forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith ([(FilePath, ByteString)] -> StaticSettings
embeddedSettings [(FilePath, ByteString)]
files)
serveDirectoryWith :: StaticSettings -> ServerT Raw m
serveDirectoryWith :: StaticSettings -> ServerT Raw m
serveDirectoryWith = Application -> Tagged m Application
forall k (s :: k) b. b -> Tagged s b
Tagged (Application -> Tagged m Application)
-> (StaticSettings -> Application)
-> StaticSettings
-> Tagged m Application
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StaticSettings -> Application
staticApp
serveDirectory :: FilePath -> ServerT Raw m
serveDirectory :: FilePath -> ServerT Raw m
serveDirectory = FilePath -> ServerT Raw m
forall (m :: * -> *). FilePath -> ServerT Raw m
serveDirectoryFileServer
{-# DEPRECATED serveDirectory "Use serveDirectoryFileServer instead" #-}
fixPath :: FilePath -> FilePath
fixPath :: FilePath -> FilePath
fixPath = FilePath -> FilePath
addTrailingPathSeparator