Skip to content

Commit 2154699

Browse files
committed
Introduce a Handler alias for ExceptT ServantErr IO
Fixes #434
1 parent b8422e8 commit 2154699

File tree

14 files changed

+115
-117
lines changed

14 files changed

+115
-117
lines changed

doc/tutorial/Authentication.lhs

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,6 @@ You can use this combinator to protect an API as follows:
4444
4545
module Authentication where
4646
47-
import Control.Monad.Trans.Except (ExceptT)
4847
import Data.Aeson (ToJSON)
4948
import Data.ByteString (ByteString)
5049
import Data.Map (Map, fromList)
@@ -66,7 +65,7 @@ import Servant.Server (BasicAuthCheck (BasicAuthCheck),
6665
),
6766
Context ((:.), EmptyContext),
6867
err401, err403, errBody, Server,
69-
ServantErr, serveWithContext)
68+
serveWithContext, Handler)
7069
import Servant.Server.Experimental.Auth (AuthHandler, AuthServerData,
7170
mkAuthHandler)
7271
import Servant.Server.Experimental.Auth()
@@ -118,22 +117,22 @@ or dictated the structure of a response (e.g. a `Capture` param is pulled from
118117
the request path). Now consider an API resource protected by basic
119118
authentication. Once the required `WWW-Authenticate` header is checked, we need
120119
to verify the username and password. But how? One solution would be to force an
121-
API author to provide a function of type `BasicAuthData -> ExceptT ServantErr IO User`
120+
API author to provide a function of type `BasicAuthData -> Handler User`
122121
and servant should use this function to authenticate a request. Unfortunately
123122
this didn't work prior to `0.5` because all of servant's machinery was
124123
engineered around the idea that each combinator can extract information from
125124
only the request. We cannot extract the function
126-
`BasicAuthData -> ExceptT ServantErr IO User` from a request! Are we doomed?
125+
`BasicAuthData -> Handler User` from a request! Are we doomed?
127126
128127
Servant `0.5` introduced `Context` to handle this. The type machinery is beyond
129128
the scope of this tutorial, but the idea is simple: provide some data to the
130129
`serve` function, and that data is propagated to the functions that handle each
131130
combinator. Using `Context`, we can supply a function of type
132-
`BasicAuthData -> ExceptT ServantErr IO User` to the `BasicAuth` combinator
131+
`BasicAuthData -> Handler User` to the `BasicAuth` combinator
133132
handler. This will allow the handler to check authentication and return a `User`
134133
to downstream handlers if successful.
135134
136-
In practice we wrap `BasicAuthData -> ExceptT ServantErr IO` into a slightly
135+
In practice we wrap `BasicAuthData -> Handler` into a slightly
137136
different function to better capture the semantics of basic authentication:
138137
139138
``` haskell ignore
@@ -247,7 +246,7 @@ your feedback!
247246
### What is Generalized Authentication?
248247
249248
**TL;DR**: you throw a tagged `AuthProtect` combinator in front of the endpoints
250-
you want protected and then supply a function `Request -> ExceptT IO ServantErr user`
249+
you want protected and then supply a function `Request -> Handler user`
251250
which we run anytime a request matches a protected endpoint. It precisely solves
252251
the "I just need to protect these endpoints with a function that does some
253252
complicated business logic" and nothing more. Behind the scenes we use a type
@@ -273,19 +272,19 @@ database = fromList [ ("key1", Account "Anne Briggs")
273272
274273
-- | A method that, when given a password, will return a Account.
275274
-- This is our bespoke (and bad) authentication logic.
276-
lookupAccount :: ByteString -> ExceptT ServantErr IO Account
275+
lookupAccount :: ByteString -> Handler Account
277276
lookupAccount key = case Map.lookup key database of
278277
Nothing -> throwError (err403 { errBody = "Invalid Cookie" })
279278
Just usr -> return usr
280279
```
281280
282281
For generalized authentication, servant exposes the `AuthHandler` type,
283-
which is used to wrap the `Request -> ExceptT IO ServantErr user` logic. Let's
282+
which is used to wrap the `Request -> Handler user` logic. Let's
284283
create a value of type `AuthHandler Request Account` using the above `lookupAccount`
285284
method:
286285
287286
```haskell
288-
-- | The auth handler wraps a function from Request -> ExceptT ServantErr IO Account
287+
-- | The auth handler wraps a function from Request -> Handler Account
289288
-- we look for a Cookie and pass the value of the cookie to `lookupAccount`.
290289
authHandler :: AuthHandler Request Account
291290
authHandler =
@@ -380,7 +379,7 @@ forward:
380379
2. choose a application-specific data type used by your server when
381380
authentication is successful (in our case this was `User`).
382381
3. Create a value of `AuthHandler Request User` which encapsulates the
383-
authentication logic (`Request -> ExceptT IO ServantErr User`). This function
382+
authentication logic (`Request -> Handler User`). This function
384383
will be executed everytime a request matches a protected route.
385384
4. Provide an instance of the `AuthServerData` type family, specifying your
386385
application-specific data type returned when authentication is successful (in

doc/tutorial/Server.lhs

Lines changed: 41 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -111,11 +111,11 @@ corresponding API type.
111111
The first thing to know about the `Server` type family is that behind the
112112
scenes it will drive the routing, letting you focus only on the business
113113
logic. The second thing to know is that for each endpoint, your handlers will
114-
by default run in the `ExceptT ServantErr IO` monad. This is overridable very
114+
by default run in the `Handler` monad. This is overridable very
115115
easily, as explained near the end of this guide. Third thing, the type of the
116116
value returned in that monad must be the same as the second argument of the
117117
HTTP method combinator used for the corresponding endpoint. In our case, it
118-
means we must provide a handler of type `ExceptT ServantErr IO [User]`. Well,
118+
means we must provide a handler of type `Handler [User]`. Well,
119119
we have a monad, let's just `return` our list:
120120
121121
``` haskell
@@ -269,15 +269,15 @@ server3 = position
269269
:<|> hello
270270
:<|> marketing
271271
272-
where position :: Int -> Int -> ExceptT ServantErr IO Position
272+
where position :: Int -> Int -> Handler Position
273273
position x y = return (Position x y)
274274
275-
hello :: Maybe String -> ExceptT ServantErr IO HelloMessage
275+
hello :: Maybe String -> Handler HelloMessage
276276
hello mname = return . HelloMessage $ case mname of
277277
Nothing -> "Hello, anonymous coward"
278278
Just n -> "Hello, " ++ n
279279
280-
marketing :: ClientInfo -> ExceptT ServantErr IO Email
280+
marketing :: ClientInfo -> Handler Email
281281
marketing clientinfo = return (emailForClient clientinfo)
282282
```
283283
@@ -307,7 +307,7 @@ $ curl -X POST -d '{"clientName":"Alp Mestanogullari", "clientEmail" : "alp@foo.
307307
308308
For reference, here's a list of some combinators from **servant**:
309309
310-
> - `Delete`, `Get`, `Patch`, `Post`, `Put`: these do not become arguments. They provide the return type of handlers, which usually is `ExceptT ServantErr IO <something>`.
310+
> - `Delete`, `Get`, `Patch`, `Post`, `Put`: these do not become arguments. They provide the return type of handlers, which usually is `Handler <something>`.
311311
> - `Capture "something" a` becomes an argument of type `a`.
312312
> - `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.
313313
> - `QueryFlag "something"` gets turned into an argument of type `Bool`.
@@ -601,11 +601,10 @@ $ curl -H 'Accept: text/html' http://localhost:8081/persons
601601
# or just point your browser to http://localhost:8081/persons
602602
```
603603
604-
## The `ExceptT ServantErr IO` monad
604+
## The `Handler` monad
605605
606-
At the heart of the handlers is the monad they run in, namely `ExceptT
607-
ServantErr IO`
608-
([haddock documentation for `ExceptT`](http://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad-Except.html#t:ExceptT)).
606+
At the heart of the handlers is the monad they run in, namely `ExceptT ServantErr IO`
607+
([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`.
609608
One might wonder: why this monad? The answer is that it is the
610609
simplest monad with the following properties:
611610
@@ -621,7 +620,7 @@ Let's recall some definitions.
621620
newtype ExceptT e m a = ExceptT (m (Either e a))
622621
```
623622
624-
In short, this means that a handler of type `ExceptT ServantErr IO a` is simply
623+
In short, this means that a handler of type `Handler a` is simply
625624
equivalent to a computation of type `IO (Either ServantErr a)`, that is, an IO
626625
action that either returns an error or a result.
627626
@@ -688,7 +687,7 @@ module. If you want to use these values but add a body or some headers, just
688687
use record update syntax:
689688
690689
``` haskell
691-
failingHandler :: ExceptT ServantErr IO ()
690+
failingHandler :: Handler ()
692691
failingHandler = throwError myerr
693692
694693
where myerr :: ServantErr
@@ -826,11 +825,11 @@ However, you have to be aware that this has an effect on the type of the
826825
corresponding `Server`:
827826
828827
``` haskell ignore
829-
Server UserAPI3 = (Int -> ExceptT ServantErr IO User)
830-
:<|> (Int -> ExceptT ServantErr IO ())
828+
Server UserAPI3 = (Int -> Handler User)
829+
:<|> (Int -> Handler ())
831830
832-
Server UserAPI4 = Int -> ( ExceptT ServantErr IO User
833-
:<|> ExceptT ServantErr IO ()
831+
Server UserAPI4 = Int -> ( Handler User
832+
:<|> Handler ()
834833
)
835834
```
836835
@@ -842,10 +841,10 @@ computations in `ExceptT`, with no arguments. In other words:
842841
server8 :: Server UserAPI3
843842
server8 = getUser :<|> deleteUser
844843
845-
where getUser :: Int -> ExceptT ServantErr IO User
844+
where getUser :: Int -> Handler User
846845
getUser _userid = error "..."
847846
848-
deleteUser :: Int -> ExceptT ServantErr IO ()
847+
deleteUser :: Int -> Handler ()
849848
deleteUser _userid = error "..."
850849
851850
-- notice how getUser and deleteUser
@@ -854,10 +853,10 @@ server8 = getUser :<|> deleteUser
854853
server9 :: Server UserAPI4
855854
server9 userid = getUser userid :<|> deleteUser userid
856855
857-
where getUser :: Int -> ExceptT ServantErr IO User
856+
where getUser :: Int -> Handler User
858857
getUser = error "..."
859858
860-
deleteUser :: Int -> ExceptT ServantErr IO ()
859+
deleteUser :: Int -> Handler ()
861860
deleteUser = error "..."
862861
```
863862
@@ -905,23 +904,23 @@ type UsersAPI =
905904
usersServer :: Server UsersAPI
906905
usersServer = getUsers :<|> newUser :<|> userOperations
907906
908-
where getUsers :: ExceptT ServantErr IO [User]
907+
where getUsers :: Handler [User]
909908
getUsers = error "..."
910909
911-
newUser :: User -> ExceptT ServantErr IO ()
910+
newUser :: User -> Handler ()
912911
newUser = error "..."
913912
914913
userOperations userid =
915914
viewUser userid :<|> updateUser userid :<|> deleteUser userid
916915
917916
where
918-
viewUser :: Int -> ExceptT ServantErr IO User
917+
viewUser :: Int -> Handler User
919918
viewUser = error "..."
920919
921-
updateUser :: Int -> User -> ExceptT ServantErr IO ()
920+
updateUser :: Int -> User -> Handler ()
922921
updateUser = error "..."
923922
924-
deleteUser :: Int -> ExceptT ServantErr IO ()
923+
deleteUser :: Int -> Handler ()
925924
deleteUser = error "..."
926925
```
927926
@@ -940,23 +939,23 @@ data Product = Product { productId :: Int }
940939
productsServer :: Server ProductsAPI
941940
productsServer = getProducts :<|> newProduct :<|> productOperations
942941
943-
where getProducts :: ExceptT ServantErr IO [Product]
942+
where getProducts :: Handler [Product]
944943
getProducts = error "..."
945944
946-
newProduct :: Product -> ExceptT ServantErr IO ()
945+
newProduct :: Product -> Handler ()
947946
newProduct = error "..."
948947
949948
productOperations productid =
950949
viewProduct productid :<|> updateProduct productid :<|> deleteProduct productid
951950
952951
where
953-
viewProduct :: Int -> ExceptT ServantErr IO Product
952+
viewProduct :: Int -> Handler Product
954953
viewProduct = error "..."
955954
956-
updateProduct :: Int -> Product -> ExceptT ServantErr IO ()
955+
updateProduct :: Int -> Product -> Handler ()
957956
updateProduct = error "..."
958957
959-
deleteProduct :: Int -> ExceptT ServantErr IO ()
958+
deleteProduct :: Int -> Handler ()
960959
deleteProduct = error "..."
961960
```
962961
@@ -985,11 +984,11 @@ type APIFor a i =
985984
986985
-- Build the appropriate 'Server'
987986
-- given the handlers of the right type.
988-
serverFor :: ExceptT ServantErr IO [a] -- handler for listing of 'a's
989-
-> (a -> ExceptT ServantErr IO ()) -- handler for adding an 'a'
990-
-> (i -> ExceptT ServantErr IO a) -- handler for viewing an 'a' given its identifier of type 'i'
991-
-> (i -> a -> ExceptT ServantErr IO ()) -- updating an 'a' with given id
992-
-> (i -> ExceptT ServantErr IO ()) -- deleting an 'a' given its id
987+
serverFor :: Handler [a] -- handler for listing of 'a's
988+
-> (a -> Handler ()) -- handler for adding an 'a'
989+
-> (i -> Handler a) -- handler for viewing an 'a' given its identifier of type 'i'
990+
-> (i -> a -> Handler ()) -- updating an 'a' with given id
991+
-> (i -> Handler ()) -- deleting an 'a' given its id
993992
-> Server (APIFor a i)
994993
serverFor = error "..."
995994
-- implementation left as an exercise. contact us on IRC
@@ -998,12 +997,11 @@ serverFor = error "..."
998997
999998
## Using another monad for your handlers
1000999
1001-
Remember how `Server` turns combinators for HTTP methods into `ExceptT
1002-
ServantErr IO`? Well, actually, there's more to that. `Server` is actually a
1000+
Remember how `Server` turns combinators for HTTP methods into `Handler`? Well, actually, there's more to that. `Server` is actually a
10031001
simple type synonym.
10041002
10051003
``` haskell ignore
1006-
type Server api = ServerT api (ExceptT ServantErr IO)
1004+
type Server api = ServerT api Handler
10071005
```
10081006
10091007
`ServerT` is the actual type family that computes the required types for the
@@ -1036,12 +1034,11 @@ listToMaybeNat = Nat listToMaybe -- from Data.Maybe
10361034
10371035
(`Nat` comes from "natural transformation", in case you're wondering.)
10381036
1039-
So if you want to write handlers using another monad/type than `ExceptT
1040-
ServantErr IO`, say the `Reader String` monad, the first thing you have to
1037+
So if you want to write handlers using another monad/type than `Handler`, say the `Reader String` monad, the first thing you have to
10411038
prepare is a function:
10421039
10431040
``` haskell ignore
1044-
readerToHandler :: Reader String :~> ExceptT ServantErr IO
1041+
readerToHandler :: Reader String :~> Handler
10451042
```
10461043
10471044
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
10501047
that function with the `Nat` constructor to make it have the fancier type.
10511048
10521049
``` haskell
1053-
readerToHandler' :: forall a. Reader String a -> ExceptT ServantErr IO a
1050+
readerToHandler' :: forall a. Reader String a -> Handler a
10541051
readerToHandler' r = return (runReader r "hi")
10551052
1056-
readerToHandler :: Reader String :~> ExceptT ServantErr IO
1053+
readerToHandler :: Reader String :~> Handler
10571054
readerToHandler = Nat readerToHandler'
10581055
```
10591056
@@ -1077,8 +1074,7 @@ readerServerT = a :<|> b
10771074
```
10781075
10791076
We unfortunately can't use `readerServerT` as an argument of `serve`, because
1080-
`serve` wants a `Server ReaderAPI`, i.e., with handlers running in `ExceptT
1081-
ServantErr IO`. But there's a simple solution to this.
1077+
`serve` wants a `Server ReaderAPI`, i.e., with handlers running in `Handler`. But there's a simple solution to this.
10821078
10831079
### Enter `enter`
10841080

servant-client/test/Servant/ClientSpec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -355,7 +355,7 @@ failSpec = beforeAll (startWaiApp failServer) $ afterAll endWaiApp $ do
355355
_ -> fail $ "expected InvalidContentTypeHeader, but got " <> show res
356356

357357
data WrappedApi where
358-
WrappedApi :: (HasServer (api :: *) '[], Server api ~ ExceptT ServantErr IO a,
358+
WrappedApi :: (HasServer (api :: *) '[], Server api ~ Handler a,
359359
HasClient api, Client api ~ (C.Manager -> BaseUrl -> SCR.ClientM ())) =>
360360
Proxy api -> WrappedApi
361361

servant-mock/src/Servant/Mock.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -97,8 +97,8 @@ class HasServer api context => HasMock api context where
9797
-- actually "means" 2 request handlers, of the following types:
9898
--
9999
-- @
100-
-- getUser :: ExceptT ServantErr IO User
101-
-- getBook :: ExceptT ServantErr IO Book
100+
-- getUser :: Handler User
101+
-- getBook :: Handler Book
102102
-- @
103103
--
104104
-- So under the hood, 'mock' uses the 'IO' bit to generate

servant-server/example/greet.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ testApi = Proxy
4444
-- There's one handler per endpoint, which, just like in the type
4545
-- that represents the API, are glued together using :<|>.
4646
--
47-
-- Each handler runs in the 'ExceptT ServantErr IO' monad.
47+
-- Each handler runs in the 'Handler' monad.
4848
server :: Server TestApi
4949
server = helloH :<|> postGreetH :<|> deleteGreetH
5050

servant-server/src/Servant/Server.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ module Servant.Server
1717
, -- * Handlers for all standard combinators
1818
HasServer(..)
1919
, Server
20+
, Handler
2021

2122
-- * Debugging the server layout
2223
, layout

servant-server/src/Servant/Server/Experimental/Auth.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -12,8 +12,7 @@
1212

1313
module Servant.Server.Experimental.Auth where
1414

15-
import Control.Monad.Trans.Except (ExceptT,
16-
runExceptT)
15+
import Control.Monad.Trans.Except (runExceptT)
1716
import Data.Proxy (Proxy (Proxy))
1817
import Data.Typeable (Typeable)
1918
import GHC.Generics (Generic)
@@ -28,7 +27,7 @@ import Servant.Server.Internal (HasContextEntry,
2827
import Servant.Server.Internal.Router (Router' (WithRequest))
2928
import Servant.Server.Internal.RoutingApplication (RouteResult (FailFatal, Route),
3029
addAuthCheck)
31-
import Servant.Server.Internal.ServantErr (ServantErr)
30+
import Servant.Server.Internal.ServantErr (ServantErr, Handler)
3231

3332
-- * General Auth
3433

@@ -42,11 +41,11 @@ type family AuthServerData a :: *
4241
--
4342
-- NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE
4443
newtype AuthHandler r usr = AuthHandler
45-
{ unAuthHandler :: r -> ExceptT ServantErr IO usr }
44+
{ unAuthHandler :: r -> Handler usr }
4645
deriving (Generic, Typeable)
4746

4847
-- | NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE
49-
mkAuthHandler :: (r -> ExceptT ServantErr IO usr) -> AuthHandler r usr
48+
mkAuthHandler :: (r -> Handler usr) -> AuthHandler r usr
5049
mkAuthHandler = AuthHandler
5150

5251
-- | Known orphan instance.

0 commit comments

Comments
 (0)