{-# 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 :: forall (m :: * -> *). FilePath -> ServerT Raw m
serveDirectoryWebApp = forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> StaticSettings
defaultWebAppSettings forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
fixPath
serveDirectoryFileServer :: FilePath -> ServerT Raw m
serveDirectoryFileServer :: forall (m :: * -> *). FilePath -> ServerT Raw m
serveDirectoryFileServer = forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> StaticSettings
defaultFileServerSettings forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
fixPath
serveDirectoryWebAppLookup :: ETagLookup -> FilePath -> ServerT Raw m
serveDirectoryWebAppLookup :: forall (m :: * -> *). ETagLookup -> FilePath -> ServerT Raw m
serveDirectoryWebAppLookup ETagLookup
etag =
forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip FilePath -> ETagLookup -> StaticSettings
webAppSettingsWithLookup ETagLookup
etag forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
fixPath
serveDirectoryEmbedded :: [(FilePath, ByteString)] -> ServerT Raw m
serveDirectoryEmbedded :: forall (m :: * -> *). [(FilePath, ByteString)] -> ServerT Raw m
serveDirectoryEmbedded [(FilePath, ByteString)]
files = forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith ([(FilePath, ByteString)] -> StaticSettings
embeddedSettings [(FilePath, ByteString)]
files)
serveDirectoryWith :: StaticSettings -> ServerT Raw m
serveDirectoryWith :: forall (m :: * -> *). StaticSettings -> ServerT Raw m
serveDirectoryWith = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. StaticSettings -> Application
staticApp
serveDirectory :: FilePath -> ServerT Raw m
serveDirectory :: forall (m :: * -> *). FilePath -> ServerT Raw m
serveDirectory = forall (m :: * -> *). FilePath -> ServerT Raw m
serveDirectoryFileServer
{-# DEPRECATED serveDirectory "Use serveDirectoryFileServer instead" #-}
fixPath :: FilePath -> FilePath
fixPath :: FilePath -> FilePath
fixPath = FilePath -> FilePath
addTrailingPathSeparator