Deprecate S.Utils.StaticFiles in favor of S.Server.StaticFiles
This commit is contained in:
parent
187c3f49d2
commit
374a7b88fb
5 changed files with 106 additions and 96 deletions
|
@ -54,6 +54,10 @@ library
|
|||
Servant.Server.Internal.Router
|
||||
Servant.Server.Internal.RoutingApplication
|
||||
Servant.Server.Internal.ServantErr
|
||||
Servant.Server.StaticFiles
|
||||
|
||||
-- deprecated
|
||||
exposed-modules:
|
||||
Servant.Utils.StaticFiles
|
||||
|
||||
-- Bundled with GHC: Lower bound to not force re-installs
|
||||
|
@ -133,12 +137,12 @@ test-suite spec
|
|||
Servant.Server.Internal.ContextSpec
|
||||
Servant.Server.Internal.RoutingApplicationSpec
|
||||
Servant.Server.RouterSpec
|
||||
Servant.Server.StaticFilesSpec
|
||||
Servant.Server.StreamingSpec
|
||||
Servant.Server.UsingContextSpec
|
||||
Servant.Server.UsingContextSpec.TestCombinators
|
||||
Servant.HoistSpec
|
||||
Servant.ServerSpec
|
||||
Servant.Utils.StaticFilesSpec
|
||||
|
||||
-- Dependencies inherited from the library. No need to specify bounds.
|
||||
build-depends:
|
||||
|
|
|
@ -7,7 +7,7 @@ module Servant (
|
|||
module Servant.Server,
|
||||
-- | Utilities on top of the servant core
|
||||
module Servant.Links,
|
||||
module Servant.Utils.StaticFiles,
|
||||
module Servant.Server.StaticFiles,
|
||||
-- | Useful re-exports
|
||||
Proxy(..),
|
||||
throwError
|
||||
|
@ -19,4 +19,4 @@ import Data.Proxy
|
|||
import Servant.API
|
||||
import Servant.Links
|
||||
import Servant.Server
|
||||
import Servant.Utils.StaticFiles
|
||||
import Servant.Server.StaticFiles
|
||||
|
|
92
servant-server/src/Servant/Server/StaticFiles.hs
Normal file
92
servant-server/src/Servant/Server/StaticFiles.hs
Normal file
|
@ -0,0 +1,92 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
-- | This module defines server-side handlers that lets you serve static files.
|
||||
--
|
||||
-- The most common needs for a web application are covered by
|
||||
-- 'serveDirectoryWebApp`, but the other variants allow you to use
|
||||
-- different `StaticSettings` and 'serveDirectoryWith' even allows you
|
||||
-- to specify arbitrary 'StaticSettings' to be used for serving static files.
|
||||
module Servant.Server.StaticFiles
|
||||
( serveDirectoryWebApp
|
||||
, serveDirectoryWebAppLookup
|
||||
, serveDirectoryFileServer
|
||||
, serveDirectoryEmbedded
|
||||
, serveDirectoryWith
|
||||
, -- * Deprecated
|
||||
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)
|
||||
#if !MIN_VERSION_wai_app_static(3,1,0)
|
||||
import Filesystem.Path.CurrentOS
|
||||
(decodeString)
|
||||
#endif
|
||||
import WaiAppStatic.Storage.Filesystem
|
||||
(ETagLookup)
|
||||
|
||||
-- | Serve anything under the specified directory as a 'Raw' endpoint.
|
||||
--
|
||||
-- @
|
||||
-- type MyApi = "static" :> Raw
|
||||
--
|
||||
-- server :: Server MyApi
|
||||
-- server = serveDirectoryWebApp "\/var\/www"
|
||||
-- @
|
||||
--
|
||||
-- would capture any request to @\/static\/\<something>@ and look for
|
||||
-- @\<something>@ under @\/var\/www@.
|
||||
--
|
||||
-- It will do its best to guess the MIME type for that file, based on the extension,
|
||||
-- and send an appropriate /Content-Type/ header if possible.
|
||||
--
|
||||
-- If your goal is to serve HTML, CSS and Javascript files that use the rest of the API
|
||||
-- as a webapp backend, you will most likely not want the static files to be hidden
|
||||
-- behind a /\/static\// prefix. In that case, remember to put the 'serveDirectoryWebApp'
|
||||
-- handler in the last position, because /servant/ will try to match the handlers
|
||||
-- in order.
|
||||
--
|
||||
-- Corresponds to the `defaultWebAppSettings` `StaticSettings` value.
|
||||
serveDirectoryWebApp :: FilePath -> ServerT Raw m
|
||||
serveDirectoryWebApp = serveDirectoryWith . defaultWebAppSettings . fixPath
|
||||
|
||||
-- | Same as 'serveDirectoryWebApp', but uses `defaultFileServerSettings`.
|
||||
serveDirectoryFileServer :: FilePath -> ServerT Raw m
|
||||
serveDirectoryFileServer = serveDirectoryWith . defaultFileServerSettings . fixPath
|
||||
|
||||
-- | Same as 'serveDirectoryWebApp', but uses 'webAppSettingsWithLookup'.
|
||||
serveDirectoryWebAppLookup :: ETagLookup -> FilePath -> ServerT Raw m
|
||||
serveDirectoryWebAppLookup etag =
|
||||
serveDirectoryWith . flip webAppSettingsWithLookup etag . fixPath
|
||||
|
||||
-- | Uses 'embeddedSettings'.
|
||||
serveDirectoryEmbedded :: [(FilePath, ByteString)] -> ServerT Raw m
|
||||
serveDirectoryEmbedded files = serveDirectoryWith (embeddedSettings files)
|
||||
|
||||
-- | Alias for 'staticApp'. Lets you serve a directory
|
||||
-- with arbitrary 'StaticSettings'. Useful when you want
|
||||
-- particular settings not covered by the four other
|
||||
-- variants. This is the most flexible method.
|
||||
serveDirectoryWith :: StaticSettings -> ServerT Raw m
|
||||
serveDirectoryWith = Tagged . staticApp
|
||||
|
||||
-- | Same as 'serveDirectoryFileServer'. It used to be the only
|
||||
-- file serving function in servant pre-0.10 and will be kept
|
||||
-- around for a few versions, but is deprecated.
|
||||
serveDirectory :: FilePath -> ServerT Raw m
|
||||
serveDirectory = serveDirectoryFileServer
|
||||
{-# DEPRECATED serveDirectory "Use serveDirectoryFileServer instead" #-}
|
||||
|
||||
fixPath :: FilePath -> FilePath
|
||||
fixPath =
|
||||
#if MIN_VERSION_wai_app_static(3,1,0)
|
||||
addTrailingPathSeparator
|
||||
#else
|
||||
decodeString . addTrailingPathSeparator
|
||||
#endif
|
|
@ -1,92 +1,6 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
-- | This module defines server-side handlers that lets you serve static files.
|
||||
--
|
||||
-- The most common needs for a web application are covered by
|
||||
-- 'serveDirectoryWebApp`, but the other variants allow you to use
|
||||
-- different `StaticSettings` and 'serveDirectoryWith' even allows you
|
||||
-- to specify arbitrary 'StaticSettings' to be used for serving static files.
|
||||
module Servant.Utils.StaticFiles
|
||||
( serveDirectoryWebApp
|
||||
, serveDirectoryWebAppLookup
|
||||
, serveDirectoryFileServer
|
||||
, serveDirectoryEmbedded
|
||||
, serveDirectoryWith
|
||||
, -- * Deprecated
|
||||
serveDirectory
|
||||
) where
|
||||
{-# DEPRECATED "Use Servant.ServerStaticFiles." #-}
|
||||
( module Servant.Server.StaticFiles )
|
||||
where
|
||||
|
||||
import Data.ByteString
|
||||
(ByteString)
|
||||
import Network.Wai.Application.Static
|
||||
import Servant.API.Raw
|
||||
(Raw)
|
||||
import Servant.Server
|
||||
(ServerT, Tagged (..))
|
||||
import System.FilePath
|
||||
(addTrailingPathSeparator)
|
||||
#if !MIN_VERSION_wai_app_static(3,1,0)
|
||||
import Filesystem.Path.CurrentOS
|
||||
(decodeString)
|
||||
#endif
|
||||
import WaiAppStatic.Storage.Filesystem
|
||||
(ETagLookup)
|
||||
|
||||
-- | Serve anything under the specified directory as a 'Raw' endpoint.
|
||||
--
|
||||
-- @
|
||||
-- type MyApi = "static" :> Raw
|
||||
--
|
||||
-- server :: Server MyApi
|
||||
-- server = serveDirectoryWebApp "\/var\/www"
|
||||
-- @
|
||||
--
|
||||
-- would capture any request to @\/static\/\<something>@ and look for
|
||||
-- @\<something>@ under @\/var\/www@.
|
||||
--
|
||||
-- It will do its best to guess the MIME type for that file, based on the extension,
|
||||
-- and send an appropriate /Content-Type/ header if possible.
|
||||
--
|
||||
-- If your goal is to serve HTML, CSS and Javascript files that use the rest of the API
|
||||
-- as a webapp backend, you will most likely not want the static files to be hidden
|
||||
-- behind a /\/static\// prefix. In that case, remember to put the 'serveDirectoryWebApp'
|
||||
-- handler in the last position, because /servant/ will try to match the handlers
|
||||
-- in order.
|
||||
--
|
||||
-- Corresponds to the `defaultWebAppSettings` `StaticSettings` value.
|
||||
serveDirectoryWebApp :: FilePath -> ServerT Raw m
|
||||
serveDirectoryWebApp = serveDirectoryWith . defaultWebAppSettings . fixPath
|
||||
|
||||
-- | Same as 'serveDirectoryWebApp', but uses `defaultFileServerSettings`.
|
||||
serveDirectoryFileServer :: FilePath -> ServerT Raw m
|
||||
serveDirectoryFileServer = serveDirectoryWith . defaultFileServerSettings . fixPath
|
||||
|
||||
-- | Same as 'serveDirectoryWebApp', but uses 'webAppSettingsWithLookup'.
|
||||
serveDirectoryWebAppLookup :: ETagLookup -> FilePath -> ServerT Raw m
|
||||
serveDirectoryWebAppLookup etag =
|
||||
serveDirectoryWith . flip webAppSettingsWithLookup etag . fixPath
|
||||
|
||||
-- | Uses 'embeddedSettings'.
|
||||
serveDirectoryEmbedded :: [(FilePath, ByteString)] -> ServerT Raw m
|
||||
serveDirectoryEmbedded files = serveDirectoryWith (embeddedSettings files)
|
||||
|
||||
-- | Alias for 'staticApp'. Lets you serve a directory
|
||||
-- with arbitrary 'StaticSettings'. Useful when you want
|
||||
-- particular settings not covered by the four other
|
||||
-- variants. This is the most flexible method.
|
||||
serveDirectoryWith :: StaticSettings -> ServerT Raw m
|
||||
serveDirectoryWith = Tagged . staticApp
|
||||
|
||||
-- | Same as 'serveDirectoryFileServer'. It used to be the only
|
||||
-- file serving function in servant pre-0.10 and will be kept
|
||||
-- around for a few versions, but is deprecated.
|
||||
serveDirectory :: FilePath -> ServerT Raw m
|
||||
serveDirectory = serveDirectoryFileServer
|
||||
{-# DEPRECATED serveDirectory "Use serveDirectoryFileServer instead" #-}
|
||||
|
||||
fixPath :: FilePath -> FilePath
|
||||
fixPath =
|
||||
#if MIN_VERSION_wai_app_static(3,1,0)
|
||||
addTrailingPathSeparator
|
||||
#else
|
||||
decodeString . addTrailingPathSeparator
|
||||
#endif
|
||||
import Servant.Server.StaticFiles
|
||||
|
|
|
@ -3,7 +3,7 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
module Servant.Utils.StaticFilesSpec where
|
||||
module Servant.Server.StaticFilesSpec where
|
||||
|
||||
import Control.Exception
|
||||
(bracket)
|
||||
|
@ -24,10 +24,10 @@ import Servant.API
|
|||
((:<|>) ((:<|>)), (:>), Capture, Get, JSON, Raw)
|
||||
import Servant.Server
|
||||
(Server, serve)
|
||||
import Servant.Server.StaticFiles
|
||||
(serveDirectoryFileServer)
|
||||
import Servant.ServerSpec
|
||||
(Person (Person))
|
||||
import Servant.Utils.StaticFiles
|
||||
(serveDirectoryFileServer)
|
||||
|
||||
type Api =
|
||||
"dummy_api" :> Capture "person_name" String :> Get '[JSON] Person
|
Loading…
Reference in a new issue