Skip to content

Commit

Permalink
Wrap Application in custom monad for Raw endpoint
Browse files Browse the repository at this point in the history
Currently handler `Raw` endpoint for is just an `Application`: a value.
This value has no access to the context of an arbitrary monad that may
be used instead of the default `Handler`.

This commit changes handler type to `m Application`, allowing the user
to do arbitrary actions in `m` prior to generating an `Application`.

This is useful to do custom logic behind `servant`s back while still
having access to the environment of user's monad.
  • Loading branch information
maksbotan committed Oct 12, 2020
1 parent 0c0fe5b commit 80df111
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 12 deletions.
12 changes: 8 additions & 4 deletions servant-server/src/Servant/Server/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ import Data.String
import Data.String.Conversions
(cs)
import Data.Tagged
(Tagged (..), retag, untag)
(Tagged (..), retag)
import qualified Data.Text as T
import Data.Typeable
import GHC.TypeLits
Expand Down Expand Up @@ -587,9 +587,9 @@ instance (KnownSymbol sym, HasServer api context)
-- > server = serveDirectory "/var/www/images"
instance HasServer Raw context where

type ServerT Raw m = Tagged m Application
type ServerT Raw m = m Application

hoistServerWithContext _ _ _ = retag
hoistServerWithContext _ _ nt s = nt s

route Proxy _ rawApplication = RawRouter $ \ env request respond -> runResourceT $ do
-- note: a Raw application doesn't register any cleanup
Expand All @@ -599,7 +599,11 @@ instance HasServer Raw context where
liftIO $ go r request respond

where go r request respond = case r of
Route app -> untag app request (respond . Route)
Route appH -> do
r' <- runHandler appH
case r' of
Left e -> respond $ FailFatal e
Right app -> app request (respond . Route)
Fail a -> respond $ Fail a
FailFatal e -> respond $ FailFatal e

Expand Down
16 changes: 8 additions & 8 deletions servant-server/src/Servant/Server/StaticFiles.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import Network.Wai.Application.Static
import Servant.API.Raw
(Raw)
import Servant.Server
(ServerT, Tagged (..))
(ServerT)
import System.FilePath
(addTrailingPathSeparator)
import WaiAppStatic.Storage.Filesystem
Expand Down Expand Up @@ -49,33 +49,33 @@ import WaiAppStatic.Storage.Filesystem
-- in order.
--
-- Corresponds to the `defaultWebAppSettings` `StaticSettings` value.
serveDirectoryWebApp :: FilePath -> ServerT Raw m
serveDirectoryWebApp :: Monad m => FilePath -> ServerT Raw m
serveDirectoryWebApp = serveDirectoryWith . defaultWebAppSettings . fixPath

-- | Same as 'serveDirectoryWebApp', but uses `defaultFileServerSettings`.
serveDirectoryFileServer :: FilePath -> ServerT Raw m
serveDirectoryFileServer :: Monad m => FilePath -> ServerT Raw m
serveDirectoryFileServer = serveDirectoryWith . defaultFileServerSettings . fixPath

-- | Same as 'serveDirectoryWebApp', but uses 'webAppSettingsWithLookup'.
serveDirectoryWebAppLookup :: ETagLookup -> FilePath -> ServerT Raw m
serveDirectoryWebAppLookup :: Monad m => ETagLookup -> FilePath -> ServerT Raw m
serveDirectoryWebAppLookup etag =
serveDirectoryWith . flip webAppSettingsWithLookup etag . fixPath

-- | Uses 'embeddedSettings'.
serveDirectoryEmbedded :: [(FilePath, ByteString)] -> ServerT Raw m
serveDirectoryEmbedded :: Monad m => [(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
serveDirectoryWith :: Monad m => StaticSettings -> ServerT Raw m
serveDirectoryWith = return . 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 :: Monad m => FilePath -> ServerT Raw m
serveDirectory = serveDirectoryFileServer
{-# DEPRECATED serveDirectory "Use serveDirectoryFileServer instead" #-}

Expand Down

0 comments on commit 80df111

Please sign in to comment.