diff --git a/doc/tutorial/Authentication.lhs b/doc/tutorial/Authentication.lhs index b699b46a..5b1c8d19 100644 --- a/doc/tutorial/Authentication.lhs +++ b/doc/tutorial/Authentication.lhs @@ -44,7 +44,6 @@ You can use this combinator to protect an API as follows: module Authentication where -import Control.Monad.Trans.Except (ExceptT) import Data.Aeson (ToJSON) import Data.ByteString (ByteString) import Data.Map (Map, fromList) @@ -66,7 +65,7 @@ import Servant.Server (BasicAuthCheck (BasicAuthCheck), ), Context ((:.), EmptyContext), err401, err403, errBody, Server, - ServantErr, serveWithContext) + serveWithContext, Handler) import Servant.Server.Experimental.Auth (AuthHandler, AuthServerData, mkAuthHandler) import Servant.Server.Experimental.Auth() @@ -118,22 +117,22 @@ or dictated the structure of a response (e.g. a `Capture` param is pulled from the request path). Now consider an API resource protected by basic authentication. Once the required `WWW-Authenticate` header is checked, we need to verify the username and password. But how? One solution would be to force an -API author to provide a function of type `BasicAuthData -> ExceptT ServantErr IO User` +API author to provide a function of type `BasicAuthData -> Handler User` and servant should use this function to authenticate a request. Unfortunately this didn't work prior to `0.5` because all of servant's machinery was engineered around the idea that each combinator can extract information from only the request. We cannot extract the function -`BasicAuthData -> ExceptT ServantErr IO User` from a request! Are we doomed? +`BasicAuthData -> Handler User` from a request! Are we doomed? Servant `0.5` introduced `Context` to handle this. The type machinery is beyond the scope of this tutorial, but the idea is simple: provide some data to the `serve` function, and that data is propagated to the functions that handle each combinator. Using `Context`, we can supply a function of type -`BasicAuthData -> ExceptT ServantErr IO User` to the `BasicAuth` combinator +`BasicAuthData -> Handler User` to the `BasicAuth` combinator handler. This will allow the handler to check authentication and return a `User` to downstream handlers if successful. -In practice we wrap `BasicAuthData -> ExceptT ServantErr IO` into a slightly +In practice we wrap `BasicAuthData -> Handler` into a slightly different function to better capture the semantics of basic authentication: ``` haskell ignore @@ -247,7 +246,7 @@ your feedback! ### What is Generalized Authentication? **TL;DR**: you throw a tagged `AuthProtect` combinator in front of the endpoints -you want protected and then supply a function `Request -> ExceptT IO ServantErr user` +you want protected and then supply a function `Request -> Handler user` which we run anytime a request matches a protected endpoint. It precisely solves the "I just need to protect these endpoints with a function that does some complicated business logic" and nothing more. Behind the scenes we use a type @@ -273,19 +272,19 @@ database = fromList [ ("key1", Account "Anne Briggs") -- | A method that, when given a password, will return a Account. -- This is our bespoke (and bad) authentication logic. -lookupAccount :: ByteString -> ExceptT ServantErr IO Account +lookupAccount :: ByteString -> Handler Account lookupAccount key = case Map.lookup key database of Nothing -> throwError (err403 { errBody = "Invalid Cookie" }) Just usr -> return usr ``` For generalized authentication, servant exposes the `AuthHandler` type, -which is used to wrap the `Request -> ExceptT IO ServantErr user` logic. Let's +which is used to wrap the `Request -> Handler user` logic. Let's create a value of type `AuthHandler Request Account` using the above `lookupAccount` method: ```haskell --- | The auth handler wraps a function from Request -> ExceptT ServantErr IO Account +-- | The auth handler wraps a function from Request -> Handler Account -- we look for a Cookie and pass the value of the cookie to `lookupAccount`. authHandler :: AuthHandler Request Account authHandler = @@ -380,7 +379,7 @@ forward: 2. choose a application-specific data type used by your server when authentication is successful (in our case this was `User`). 3. Create a value of `AuthHandler Request User` which encapsulates the -authentication logic (`Request -> ExceptT IO ServantErr User`). This function +authentication logic (`Request -> Handler User`). This function will be executed everytime a request matches a protected route. 4. Provide an instance of the `AuthServerData` type family, specifying your application-specific data type returned when authentication is successful (in diff --git a/doc/tutorial/Server.lhs b/doc/tutorial/Server.lhs index bd84b8a0..af3fe17d 100644 --- a/doc/tutorial/Server.lhs +++ b/doc/tutorial/Server.lhs @@ -111,11 +111,11 @@ corresponding API type. The first thing to know about the `Server` type family is that behind the scenes it will drive the routing, letting you focus only on the business logic. The second thing to know is that for each endpoint, your handlers will -by default run in the `ExceptT ServantErr IO` monad. This is overridable very +by default run in the `Handler` monad. This is overridable very easily, as explained near the end of this guide. Third thing, the type of the value returned in that monad must be the same as the second argument of the HTTP method combinator used for the corresponding endpoint. In our case, it -means we must provide a handler of type `ExceptT ServantErr IO [User]`. Well, +means we must provide a handler of type `Handler [User]`. Well, we have a monad, let's just `return` our list: ``` haskell @@ -269,15 +269,15 @@ server3 = position :<|> hello :<|> marketing - where position :: Int -> Int -> ExceptT ServantErr IO Position + where position :: Int -> Int -> Handler Position position x y = return (Position x y) - hello :: Maybe String -> ExceptT ServantErr IO HelloMessage + hello :: Maybe String -> Handler HelloMessage hello mname = return . HelloMessage $ case mname of Nothing -> "Hello, anonymous coward" Just n -> "Hello, " ++ n - marketing :: ClientInfo -> ExceptT ServantErr IO Email + marketing :: ClientInfo -> Handler Email marketing clientinfo = return (emailForClient clientinfo) ``` @@ -307,7 +307,7 @@ $ curl -X POST -d '{"clientName":"Alp Mestanogullari", "clientEmail" : "alp@foo. For reference, here's a list of some combinators from **servant**: - > - `Delete`, `Get`, `Patch`, `Post`, `Put`: these do not become arguments. They provide the return type of handlers, which usually is `ExceptT ServantErr IO `. + > - `Delete`, `Get`, `Patch`, `Post`, `Put`: these do not become arguments. They provide the return type of handlers, which usually is `Handler `. > - `Capture "something" a` becomes an argument of type `a`. > - `QueryParam "something" a`, `Header "something" a` all become arguments of type `Maybe a`, because there might be no value at all specified by the client for these. > - `QueryFlag "something"` gets turned into an argument of type `Bool`. @@ -601,11 +601,10 @@ $ curl -H 'Accept: text/html' http://localhost:8081/persons # or just point your browser to http://localhost:8081/persons ``` -## The `ExceptT ServantErr IO` monad +## The `Handler` monad -At the heart of the handlers is the monad they run in, namely `ExceptT -ServantErr IO` -([haddock documentation for `ExceptT`](http://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad-Except.html#t:ExceptT)). +At the heart of the handlers is the monad they run in, namely `ExceptT ServantErr IO` +([haddock documentation for `ExceptT`](http://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad-Except.html#t:ExceptT)), which is aliased as `Handler`. One might wonder: why this monad? The answer is that it is the simplest monad with the following properties: @@ -621,7 +620,7 @@ Let's recall some definitions. newtype ExceptT e m a = ExceptT (m (Either e a)) ``` -In short, this means that a handler of type `ExceptT ServantErr IO a` is simply +In short, this means that a handler of type `Handler a` is simply equivalent to a computation of type `IO (Either ServantErr a)`, that is, an IO action that either returns an error or a result. @@ -688,7 +687,7 @@ module. If you want to use these values but add a body or some headers, just use record update syntax: ``` haskell -failingHandler :: ExceptT ServantErr IO () +failingHandler :: Handler () failingHandler = throwError myerr where myerr :: ServantErr @@ -826,11 +825,11 @@ However, you have to be aware that this has an effect on the type of the corresponding `Server`: ``` haskell ignore -Server UserAPI3 = (Int -> ExceptT ServantErr IO User) - :<|> (Int -> ExceptT ServantErr IO ()) +Server UserAPI3 = (Int -> Handler User) + :<|> (Int -> Handler ()) -Server UserAPI4 = Int -> ( ExceptT ServantErr IO User - :<|> ExceptT ServantErr IO () +Server UserAPI4 = Int -> ( Handler User + :<|> Handler () ) ``` @@ -842,10 +841,10 @@ computations in `ExceptT`, with no arguments. In other words: server8 :: Server UserAPI3 server8 = getUser :<|> deleteUser - where getUser :: Int -> ExceptT ServantErr IO User + where getUser :: Int -> Handler User getUser _userid = error "..." - deleteUser :: Int -> ExceptT ServantErr IO () + deleteUser :: Int -> Handler () deleteUser _userid = error "..." -- notice how getUser and deleteUser @@ -854,10 +853,10 @@ server8 = getUser :<|> deleteUser server9 :: Server UserAPI4 server9 userid = getUser userid :<|> deleteUser userid - where getUser :: Int -> ExceptT ServantErr IO User + where getUser :: Int -> Handler User getUser = error "..." - deleteUser :: Int -> ExceptT ServantErr IO () + deleteUser :: Int -> Handler () deleteUser = error "..." ``` @@ -905,23 +904,23 @@ type UsersAPI = usersServer :: Server UsersAPI usersServer = getUsers :<|> newUser :<|> userOperations - where getUsers :: ExceptT ServantErr IO [User] + where getUsers :: Handler [User] getUsers = error "..." - newUser :: User -> ExceptT ServantErr IO () + newUser :: User -> Handler () newUser = error "..." userOperations userid = viewUser userid :<|> updateUser userid :<|> deleteUser userid where - viewUser :: Int -> ExceptT ServantErr IO User + viewUser :: Int -> Handler User viewUser = error "..." - updateUser :: Int -> User -> ExceptT ServantErr IO () + updateUser :: Int -> User -> Handler () updateUser = error "..." - deleteUser :: Int -> ExceptT ServantErr IO () + deleteUser :: Int -> Handler () deleteUser = error "..." ``` @@ -940,23 +939,23 @@ data Product = Product { productId :: Int } productsServer :: Server ProductsAPI productsServer = getProducts :<|> newProduct :<|> productOperations - where getProducts :: ExceptT ServantErr IO [Product] + where getProducts :: Handler [Product] getProducts = error "..." - newProduct :: Product -> ExceptT ServantErr IO () + newProduct :: Product -> Handler () newProduct = error "..." productOperations productid = viewProduct productid :<|> updateProduct productid :<|> deleteProduct productid where - viewProduct :: Int -> ExceptT ServantErr IO Product + viewProduct :: Int -> Handler Product viewProduct = error "..." - updateProduct :: Int -> Product -> ExceptT ServantErr IO () + updateProduct :: Int -> Product -> Handler () updateProduct = error "..." - deleteProduct :: Int -> ExceptT ServantErr IO () + deleteProduct :: Int -> Handler () deleteProduct = error "..." ``` @@ -985,11 +984,11 @@ type APIFor a i = -- Build the appropriate 'Server' -- given the handlers of the right type. -serverFor :: ExceptT ServantErr IO [a] -- handler for listing of 'a's - -> (a -> ExceptT ServantErr IO ()) -- handler for adding an 'a' - -> (i -> ExceptT ServantErr IO a) -- handler for viewing an 'a' given its identifier of type 'i' - -> (i -> a -> ExceptT ServantErr IO ()) -- updating an 'a' with given id - -> (i -> ExceptT ServantErr IO ()) -- deleting an 'a' given its id +serverFor :: Handler [a] -- handler for listing of 'a's + -> (a -> Handler ()) -- handler for adding an 'a' + -> (i -> Handler a) -- handler for viewing an 'a' given its identifier of type 'i' + -> (i -> a -> Handler ()) -- updating an 'a' with given id + -> (i -> Handler ()) -- deleting an 'a' given its id -> Server (APIFor a i) serverFor = error "..." -- implementation left as an exercise. contact us on IRC @@ -998,12 +997,11 @@ serverFor = error "..." ## Using another monad for your handlers -Remember how `Server` turns combinators for HTTP methods into `ExceptT -ServantErr IO`? Well, actually, there's more to that. `Server` is actually a +Remember how `Server` turns combinators for HTTP methods into `Handler`? Well, actually, there's more to that. `Server` is actually a simple type synonym. ``` haskell ignore -type Server api = ServerT api (ExceptT ServantErr IO) +type Server api = ServerT api Handler ``` `ServerT` is the actual type family that computes the required types for the @@ -1036,12 +1034,11 @@ listToMaybeNat = Nat listToMaybe -- from Data.Maybe (`Nat` comes from "natural transformation", in case you're wondering.) -So if you want to write handlers using another monad/type than `ExceptT -ServantErr IO`, say the `Reader String` monad, the first thing you have to +So if you want to write handlers using another monad/type than `Handler`, say the `Reader String` monad, the first thing you have to prepare is a function: ``` haskell ignore -readerToHandler :: Reader String :~> ExceptT ServantErr IO +readerToHandler :: Reader String :~> Handler ``` Let's start with `readerToHandler'`. We obviously have to run the `Reader` @@ -1050,10 +1047,10 @@ from that and can then just `return` it into `ExceptT`. We can then just wrap that function with the `Nat` constructor to make it have the fancier type. ``` haskell -readerToHandler' :: forall a. Reader String a -> ExceptT ServantErr IO a +readerToHandler' :: forall a. Reader String a -> Handler a readerToHandler' r = return (runReader r "hi") -readerToHandler :: Reader String :~> ExceptT ServantErr IO +readerToHandler :: Reader String :~> Handler readerToHandler = Nat readerToHandler' ``` @@ -1077,8 +1074,7 @@ readerServerT = a :<|> b ``` We unfortunately can't use `readerServerT` as an argument of `serve`, because -`serve` wants a `Server ReaderAPI`, i.e., with handlers running in `ExceptT -ServantErr IO`. But there's a simple solution to this. +`serve` wants a `Server ReaderAPI`, i.e., with handlers running in `Handler`. But there's a simple solution to this. ### Enter `enter` diff --git a/servant-client/test/Servant/ClientSpec.hs b/servant-client/test/Servant/ClientSpec.hs index 2263e9e2..17048593 100644 --- a/servant-client/test/Servant/ClientSpec.hs +++ b/servant-client/test/Servant/ClientSpec.hs @@ -355,7 +355,7 @@ failSpec = beforeAll (startWaiApp failServer) $ afterAll endWaiApp $ do _ -> fail $ "expected InvalidContentTypeHeader, but got " <> show res data WrappedApi where - WrappedApi :: (HasServer (api :: *) '[], Server api ~ ExceptT ServantErr IO a, + WrappedApi :: (HasServer (api :: *) '[], Server api ~ Handler a, HasClient api, Client api ~ (C.Manager -> BaseUrl -> SCR.ClientM ())) => Proxy api -> WrappedApi diff --git a/servant-mock/src/Servant/Mock.hs b/servant-mock/src/Servant/Mock.hs index 881d9e84..bb999386 100644 --- a/servant-mock/src/Servant/Mock.hs +++ b/servant-mock/src/Servant/Mock.hs @@ -97,8 +97,8 @@ class HasServer api context => HasMock api context where -- actually "means" 2 request handlers, of the following types: -- -- @ - -- getUser :: ExceptT ServantErr IO User - -- getBook :: ExceptT ServantErr IO Book + -- getUser :: Handler User + -- getBook :: Handler Book -- @ -- -- So under the hood, 'mock' uses the 'IO' bit to generate diff --git a/servant-server/example/greet.hs b/servant-server/example/greet.hs index 3fda367d..67819eb0 100644 --- a/servant-server/example/greet.hs +++ b/servant-server/example/greet.hs @@ -44,7 +44,7 @@ testApi = Proxy -- There's one handler per endpoint, which, just like in the type -- that represents the API, are glued together using :<|>. -- --- Each handler runs in the 'ExceptT ServantErr IO' monad. +-- Each handler runs in the 'Handler' monad. server :: Server TestApi server = helloH :<|> postGreetH :<|> deleteGreetH diff --git a/servant-server/src/Servant/Server.hs b/servant-server/src/Servant/Server.hs index 54797c6b..b2cf7a66 100644 --- a/servant-server/src/Servant/Server.hs +++ b/servant-server/src/Servant/Server.hs @@ -17,6 +17,7 @@ module Servant.Server , -- * Handlers for all standard combinators HasServer(..) , Server + , Handler -- * Debugging the server layout , layout diff --git a/servant-server/src/Servant/Server/Experimental/Auth.hs b/servant-server/src/Servant/Server/Experimental/Auth.hs index d40bbd20..86d4dc03 100644 --- a/servant-server/src/Servant/Server/Experimental/Auth.hs +++ b/servant-server/src/Servant/Server/Experimental/Auth.hs @@ -12,8 +12,7 @@ module Servant.Server.Experimental.Auth where -import Control.Monad.Trans.Except (ExceptT, - runExceptT) +import Control.Monad.Trans.Except (runExceptT) import Data.Proxy (Proxy (Proxy)) import Data.Typeable (Typeable) import GHC.Generics (Generic) @@ -28,7 +27,7 @@ import Servant.Server.Internal (HasContextEntry, import Servant.Server.Internal.Router (Router' (WithRequest)) import Servant.Server.Internal.RoutingApplication (RouteResult (FailFatal, Route), addAuthCheck) -import Servant.Server.Internal.ServantErr (ServantErr) +import Servant.Server.Internal.ServantErr (ServantErr, Handler) -- * General Auth @@ -42,11 +41,11 @@ type family AuthServerData a :: * -- -- NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE newtype AuthHandler r usr = AuthHandler - { unAuthHandler :: r -> ExceptT ServantErr IO usr } + { unAuthHandler :: r -> Handler usr } deriving (Generic, Typeable) -- | NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE -mkAuthHandler :: (r -> ExceptT ServantErr IO usr) -> AuthHandler r usr +mkAuthHandler :: (r -> Handler usr) -> AuthHandler r usr mkAuthHandler = AuthHandler -- | Known orphan instance. diff --git a/servant-server/src/Servant/Server/Internal.hs b/servant-server/src/Servant/Server/Internal.hs index dbf89dd2..eb3ca19c 100644 --- a/servant-server/src/Servant/Server/Internal.hs +++ b/servant-server/src/Servant/Server/Internal.hs @@ -22,7 +22,6 @@ module Servant.Server.Internal , module Servant.Server.Internal.ServantErr ) where -import Control.Monad.Trans.Except (ExceptT) import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC8 import qualified Data.ByteString.Lazy as BL @@ -73,7 +72,7 @@ class HasServer layout context where route :: Proxy layout -> Context context -> Delayed (Server layout) -> Router -type Server layout = ServerT layout (ExceptT ServantErr IO) +type Server layout = ServerT layout Handler -- * Instances @@ -112,7 +111,7 @@ instance (HasServer a context, HasServer b context) => HasServer (a :<|> b) cont -- > -- > server :: Server MyApi -- > server = getBook --- > where getBook :: Text -> ExceptT ServantErr IO Book +-- > where getBook :: Text -> Handler Book -- > getBook isbn = ... instance (KnownSymbol capture, FromHttpApiData a, HasServer sublayout context) => HasServer (Capture capture a :> sublayout) context where @@ -157,7 +156,7 @@ acceptCheck proxy accH methodRouter :: (AllCTRender ctypes a) => Method -> Proxy ctypes -> Status - -> Delayed (ExceptT ServantErr IO a) + -> Delayed (Handler a) -> Router methodRouter method proxy status action = leafRouter route' where @@ -171,7 +170,7 @@ methodRouter method proxy status action = leafRouter route' methodRouterHeaders :: (GetHeaders (Headers h v), AllCTRender ctypes v) => Method -> Proxy ctypes -> Status - -> Delayed (ExceptT ServantErr IO (Headers h v)) + -> Delayed (Handler (Headers h v)) -> Router methodRouterHeaders method proxy status action = leafRouter route' where @@ -223,7 +222,7 @@ instance OVERLAPPING_ -- > -- > server :: Server MyApi -- > server = viewReferer --- > where viewReferer :: Referer -> ExceptT ServantErr IO referer +-- > where viewReferer :: Referer -> Handler referer -- > viewReferer referer = return referer instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context) => HasServer (Header sym a :> sublayout) context where @@ -254,7 +253,7 @@ instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context) -- > -- > server :: Server MyApi -- > server = getBooksBy --- > where getBooksBy :: Maybe Text -> ExceptT ServantErr IO [Book] +-- > where getBooksBy :: Maybe Text -> Handler [Book] -- > getBooksBy Nothing = ...return all books... -- > getBooksBy (Just author) = ...return books by the given author... instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context) @@ -291,7 +290,7 @@ instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context) -- > -- > server :: Server MyApi -- > server = getBooksBy --- > where getBooksBy :: [Text] -> ExceptT ServantErr IO [Book] +-- > where getBooksBy :: [Text] -> Handler [Book] -- > getBooksBy authors = ...return all books by these authors... instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context) => HasServer (QueryParams sym a :> sublayout) context where @@ -322,7 +321,7 @@ instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context) -- > -- > server :: Server MyApi -- > server = getBooks --- > where getBooks :: Bool -> ExceptT ServantErr IO [Book] +-- > where getBooks :: Bool -> Handler [Book] -- > getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument... instance (KnownSymbol sym, HasServer sublayout context) => HasServer (QueryFlag sym :> sublayout) context where @@ -379,7 +378,7 @@ instance HasServer Raw context where -- > -- > server :: Server MyApi -- > server = postBook --- > where postBook :: Book -> ExceptT ServantErr IO Book +-- > where postBook :: Book -> Handler Book -- > postBook book = ...insert into your db... instance ( AllCTUnrender list a, HasServer sublayout context ) => HasServer (ReqBody list a :> sublayout) context where diff --git a/servant-server/src/Servant/Server/Internal/RoutingApplication.hs b/servant-server/src/Servant/Server/Internal/RoutingApplication.hs index 56754c1f..99def4b8 100644 --- a/servant-server/src/Servant/Server/Internal/RoutingApplication.hs +++ b/servant-server/src/Servant/Server/Internal/RoutingApplication.hs @@ -8,7 +8,7 @@ {-# LANGUAGE StandaloneDeriving #-} module Servant.Server.Internal.RoutingApplication where -import Control.Monad.Trans.Except (ExceptT, runExceptT) +import Control.Monad.Trans.Except (runExceptT) import Network.Wai (Application, Request, Response, ResponseReceived) import Prelude () @@ -222,7 +222,7 @@ runDelayed Delayed{..} = -- Takes a continuation that lets us send a response. -- Also takes a continuation for how to turn the -- result of the delayed server into a response. -runAction :: Delayed (ExceptT ServantErr IO a) +runAction :: Delayed (Handler a) -> (RouteResult Response -> IO r) -> (a -> RouteResult Response) -> IO r diff --git a/servant-server/src/Servant/Server/Internal/ServantErr.hs b/servant-server/src/Servant/Server/Internal/ServantErr.hs index 4e646a7a..b60f042c 100644 --- a/servant-server/src/Servant/Server/Internal/ServantErr.hs +++ b/servant-server/src/Servant/Server/Internal/ServantErr.hs @@ -4,6 +4,7 @@ module Servant.Server.Internal.ServantErr where import Control.Exception (Exception) +import Control.Monad.Trans.Except (ExceptT) import qualified Data.ByteString.Char8 as BS import qualified Data.ByteString.Lazy as LBS import Data.Typeable (Typeable) @@ -18,6 +19,8 @@ data ServantErr = ServantErr { errHTTPCode :: Int instance Exception ServantErr +type Handler = ExceptT ServantErr IO + responseServantErr :: ServantErr -> Response responseServantErr ServantErr{..} = responseLBS status errHeaders errBody where @@ -27,7 +30,7 @@ responseServantErr ServantErr{..} = responseLBS status errHeaders errBody -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err300 { errBody = "I can't choose." } -- err300 :: ServantErr @@ -41,7 +44,7 @@ err300 = ServantErr { errHTTPCode = 300 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err301 -- err301 :: ServantErr @@ -55,7 +58,7 @@ err301 = ServantErr { errHTTPCode = 301 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err302 -- err302 :: ServantErr @@ -69,7 +72,7 @@ err302 = ServantErr { errHTTPCode = 302 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err303 -- err303 :: ServantErr @@ -83,7 +86,7 @@ err303 = ServantErr { errHTTPCode = 303 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err304 -- err304 :: ServantErr @@ -97,7 +100,7 @@ err304 = ServantErr { errHTTPCode = 304 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err305 -- err305 :: ServantErr @@ -111,7 +114,7 @@ err305 = ServantErr { errHTTPCode = 305 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err307 -- err307 :: ServantErr @@ -125,7 +128,7 @@ err307 = ServantErr { errHTTPCode = 307 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err400 { errBody = "Your request makes no sense to me." } -- err400 :: ServantErr @@ -139,7 +142,7 @@ err400 = ServantErr { errHTTPCode = 400 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err401 { errBody = "Your credentials are invalid." } -- err401 :: ServantErr @@ -153,7 +156,7 @@ err401 = ServantErr { errHTTPCode = 401 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err402 { errBody = "You have 0 credits. Please give me $$$." } -- err402 :: ServantErr @@ -167,7 +170,7 @@ err402 = ServantErr { errHTTPCode = 402 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err403 { errBody = "Please login first." } -- err403 :: ServantErr @@ -181,7 +184,7 @@ err403 = ServantErr { errHTTPCode = 403 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err404 { errBody = "(╯°□°)╯︵ ┻━┻)." } -- err404 :: ServantErr @@ -195,7 +198,7 @@ err404 = ServantErr { errHTTPCode = 404 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err405 { errBody = "Your account privileges does not allow for this. Please pay $$$." } -- err405 :: ServantErr @@ -209,7 +212,7 @@ err405 = ServantErr { errHTTPCode = 405 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err406 -- err406 :: ServantErr @@ -223,7 +226,7 @@ err406 = ServantErr { errHTTPCode = 406 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err407 -- err407 :: ServantErr @@ -237,7 +240,7 @@ err407 = ServantErr { errHTTPCode = 407 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err409 { errBody = "Transaction conflicts with 59879cb56c7c159231eeacdd503d755f7e835f74" } -- err409 :: ServantErr @@ -251,7 +254,7 @@ err409 = ServantErr { errHTTPCode = 409 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err410 { errBody = "I know it was here at some point, but.. I blame bad luck." } -- err410 :: ServantErr @@ -265,7 +268,7 @@ err410 = ServantErr { errHTTPCode = 410 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr err411 -- err411 :: ServantErr @@ -279,7 +282,7 @@ err411 = ServantErr { errHTTPCode = 411 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err412 { errBody = "Precondition fail: x < 42 && y > 57" } -- err412 :: ServantErr @@ -293,7 +296,7 @@ err412 = ServantErr { errHTTPCode = 412 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err413 { errBody = "Request exceeded 64k." } -- err413 :: ServantErr @@ -307,7 +310,7 @@ err413 = ServantErr { errHTTPCode = 413 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err414 { errBody = "Maximum length is 64." } -- err414 :: ServantErr @@ -321,7 +324,7 @@ err414 = ServantErr { errHTTPCode = 414 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err415 { errBody = "Supported media types: gif, png" } -- err415 :: ServantErr @@ -335,7 +338,7 @@ err415 = ServantErr { errHTTPCode = 415 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err416 { errBody = "Valid range is [0, 424242]." } -- err416 :: ServantErr @@ -349,7 +352,7 @@ err416 = ServantErr { errHTTPCode = 416 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err417 { errBody = "I found a quux in the request. This isn't going to work." } -- err417 :: ServantErr @@ -363,7 +366,7 @@ err417 = ServantErr { errHTTPCode = 417 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err500 { errBody = "Exception in module A.B.C:55. Have a great day!" } -- err500 :: ServantErr @@ -377,7 +380,7 @@ err500 = ServantErr { errHTTPCode = 500 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err501 { errBody = "/v1/foo is not supported with quux in the request." } -- err501 :: ServantErr @@ -391,7 +394,7 @@ err501 = ServantErr { errHTTPCode = 501 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err502 { errBody = "Tried gateway foo, bar, and baz. None responded." } -- err502 :: ServantErr @@ -405,7 +408,7 @@ err502 = ServantErr { errHTTPCode = 502 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err503 { errBody = "We're rewriting in PHP." } -- err503 :: ServantErr @@ -419,7 +422,7 @@ err503 = ServantErr { errHTTPCode = 503 -- -- Example: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err504 { errBody = "Backend foobar did not respond in 5 seconds." } -- err504 :: ServantErr @@ -433,7 +436,7 @@ err504 = ServantErr { errHTTPCode = 504 -- -- Example usage: -- --- > failingHandler :: ExceptT ServantErr IO () +-- > failingHandler :: Handler () -- > failingHandler = throwErr $ err505 { errBody = "I support HTTP/4.0 only." } -- err505 :: ServantErr diff --git a/servant-server/test/Servant/Server/Internal/EnterSpec.hs b/servant-server/test/Servant/Server/Internal/EnterSpec.hs index 8b450377..1591e987 100644 --- a/servant-server/test/Servant/Server/Internal/EnterSpec.hs +++ b/servant-server/test/Servant/Server/Internal/EnterSpec.hs @@ -34,7 +34,7 @@ combinedAPI = Proxy readerServer' :: ServerT ReaderAPI (Reader String) readerServer' = return 1797 :<|> ask -fReader :: Reader String :~> ExceptT ServantErr IO +fReader :: Reader String :~> Handler fReader = generalizeNat C.. (runReaderTNat "hi") readerServer :: Server ReaderAPI diff --git a/servant-server/test/Servant/Server/StreamingSpec.hs b/servant-server/test/Servant/Server/StreamingSpec.hs index 3752df49..ed289257 100644 --- a/servant-server/test/Servant/Server/StreamingSpec.hs +++ b/servant-server/test/Servant/Server/StreamingSpec.hs @@ -9,7 +9,7 @@ module Servant.Server.StreamingSpec where import Control.Concurrent -import Control.Exception +import Control.Exception hiding (Handler) import Control.Monad.IO.Class import Control.Monad.Trans.Except import qualified Data.ByteString as Strict @@ -66,7 +66,7 @@ spec = do -- - receives the first chunk -- - notifies serverReceivedFirstChunk -- - receives the rest of the request - let handler :: Lazy.ByteString -> ExceptT ServantErr IO NoContent + let handler :: Lazy.ByteString -> Handler NoContent handler input = liftIO $ do let prefix = Lazy.take 3 input prefix `shouldBe` "foo" diff --git a/servant-server/test/Servant/Server/UsingContextSpec.hs b/servant-server/test/Servant/Server/UsingContextSpec.hs index 33b04125..1f9c3328 100644 --- a/servant-server/test/Servant/Server/UsingContextSpec.hs +++ b/servant-server/test/Servant/Server/UsingContextSpec.hs @@ -25,7 +25,7 @@ spec = do type OneEntryAPI = ExtractFromContext :> Get '[JSON] String -testServer :: String -> ExceptT ServantErr IO String +testServer :: String -> Handler String testServer s = return s oneEntryApp :: Application diff --git a/servant-server/test/Servant/ServerSpec.hs b/servant-server/test/Servant/ServerSpec.hs index d210ca55..5b4154d7 100644 --- a/servant-server/test/Servant/ServerSpec.hs +++ b/servant-server/test/Servant/ServerSpec.hs @@ -14,7 +14,7 @@ module Servant.ServerSpec where import Control.Monad (forM_, when, unless) -import Control.Monad.Trans.Except (ExceptT, throwE) +import Control.Monad.Trans.Except (throwE) import Data.Aeson (FromJSON, ToJSON, decode', encode) import qualified Data.ByteString.Base64 as Base64 import Data.ByteString.Conversion () @@ -48,8 +48,9 @@ import Servant.API ((:<|>) (..), (:>), AuthProtect, Raw, RemoteHost, ReqBody, StdMethod (..), Verb, addHeader) import Servant.API.Internal.Test.ComprehensiveAPI -import Servant.Server (ServantErr (..), Server, err401, err403, err404, - serve, serveWithContext, Context((:.), EmptyContext)) +import Servant.Server (ServantErr (..), Server, Handler, err401, err403, + err404, serve, serveWithContext, + Context((:.), EmptyContext)) import Test.Hspec (Spec, context, describe, it, shouldBe, shouldContain) import qualified Test.Hspec.Wai as THW @@ -180,7 +181,7 @@ verbSpec = describe "Servant.API.Verb" $ do type CaptureApi = Capture "legs" Integer :> Get '[JSON] Animal captureApi :: Proxy CaptureApi captureApi = Proxy -captureServer :: Integer -> ExceptT ServantErr IO Animal +captureServer :: Integer -> Handler Animal captureServer legs = case legs of 4 -> return jerry 2 -> return tweety @@ -336,11 +337,11 @@ headerApi = Proxy headerSpec :: Spec headerSpec = describe "Servant.API.Header" $ do - let expectsInt :: Maybe Int -> ExceptT ServantErr IO () + let expectsInt :: Maybe Int -> Handler () expectsInt (Just x) = when (x /= 5) $ error "Expected 5" expectsInt Nothing = error "Expected an int" - let expectsString :: Maybe String -> ExceptT ServantErr IO () + let expectsString :: Maybe String -> Handler () expectsString (Just x) = when (x /= "more from you") $ error "Expected more from you" expectsString Nothing = error "Expected a string"