Skip to content

Commit 751350b

Browse files
WithResource combinator for Servant-managed resources (#1630)
1 parent a4194dc commit 751350b

File tree

17 files changed

+255
-11
lines changed

17 files changed

+255
-11
lines changed

cabal.project

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ packages:
4747
doc/cookbook/using-custom-monad
4848
doc/cookbook/using-free-client
4949
-- doc/cookbook/open-id-connect
50+
doc/cookbook/managed-resource
5051

5152
tests: True
5253
optimization: False

doc/cookbook/index.rst

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,3 +37,4 @@ you name it!
3737
sentry/Sentry.lhs
3838
testing/Testing.lhs
3939
open-id-connect/OpenIdConnect.lhs
40+
managed-resource/ManagedResource.lhs
Lines changed: 114 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,114 @@
1+
# Request-lifetime Managed Resources
2+
3+
Let's see how we can write a handle that uses a resource managed by Servant. The resource is created automatically by Servant when the server recieves a request, and the resource is automatically destroyed when the server is finished handling a request.
4+
5+
As usual, we start with a little bit of throat clearing.
6+
7+
8+
``` haskell
9+
{-# LANGUAGE DataKinds #-}
10+
{-# LANGUAGE TypeOperators #-}
11+
import Control.Concurrent
12+
import Control.Exception (bracket, throwIO)
13+
import Control.Monad.IO.Class
14+
import Control.Monad.Trans.Resource
15+
import Data.Acquire
16+
import Network.HTTP.Client (newManager, defaultManagerSettings)
17+
import Network.Wai.Handler.Warp
18+
import Servant
19+
import Servant.Client
20+
import System.IO
21+
```
22+
23+
Here we define an API type that uses the `WithResource` combinator. The server handler for an endpoint with a `WithResource res` component will receive a value of that type as an argument.
24+
25+
``` haskell
26+
type API = WithResource Handle :> ReqBody '[PlainText] String :> Post '[JSON] NoContent
27+
28+
api :: Proxy API
29+
api = Proxy
30+
```
31+
32+
But this resource value has to come from somewhere. Servant obtains the value using an Acquire provided in the context. The Acquire knows how to both create and destroy resources of a particular type.
33+
34+
``` haskell
35+
appContext :: Context '[Acquire Handle]
36+
appContext = acquireHandle :. EmptyContext
37+
38+
acquireHandle :: Acquire Handle
39+
acquireHandle = mkAcquire newHandle closeHandle
40+
41+
newHandle :: IO Handle
42+
newHandle = do
43+
putStrLn "opening file"
44+
h <- openFile "test.txt" AppendMode
45+
putStrLn "opened file"
46+
return h
47+
48+
closeHandle :: Handle -> IO ()
49+
closeHandle h = do
50+
putStrLn "closing file"
51+
hClose h
52+
putStrLn "closed file"
53+
```
54+
55+
Now we create the handler which will use this resource. This handler will write the request message to the System.IO.Handle which was provided to us. In some situations the handler will succeed, but in some in will fail. In either case, Servant will clean up the resource for us.
56+
57+
``` haskell
58+
server :: Server API
59+
server = writeToFile
60+
61+
where writeToFile :: (ReleaseKey, Handle) -> String -> Handler NoContent
62+
writeToFile (_, h) msg = case msg of
63+
"illegal" -> error "wait, that's illegal!"
64+
legalMsg -> liftIO $ do
65+
putStrLn "writing file"
66+
hPutStrLn h legalMsg
67+
putStrLn "wrote file"
68+
return NoContent
69+
```
70+
71+
Finally we run the server in the background while we post messages to it.
72+
73+
``` haskell
74+
runApp :: IO ()
75+
runApp = run 8080 (serveWithContext api appContext $ server)
76+
77+
postMsg :: String -> ClientM NoContent
78+
postMsg = client api
79+
80+
main :: IO ()
81+
main = do
82+
mgr <- newManager defaultManagerSettings
83+
bracket (forkIO $ runApp) killThread $ \_ -> do
84+
ms <- flip runClientM (mkClientEnv mgr (BaseUrl Http "localhost" 8080 "")) $ do
85+
liftIO $ putStrLn "sending hello message"
86+
_ <- postMsg "hello"
87+
liftIO $ putStrLn "sending illegal message"
88+
_ <- postMsg "illegal"
89+
liftIO $ putStrLn "done"
90+
print ms
91+
```
92+
93+
This program prints
94+
95+
```
96+
sending hello message
97+
opening file
98+
opened file
99+
writing file
100+
wrote file
101+
closing file
102+
closed file
103+
sending illegal message
104+
opening file
105+
opened file
106+
closing file
107+
closed file
108+
wait, that's illegal!
109+
CallStack (from HasCallStack):
110+
error, called at ManagedResource.lhs:63:24 in main:Main
111+
Left (FailureResponse (Request {requestPath = (BaseUrl {baseUrlScheme = Http, baseUrlHost = "localhost", baseUrlPort = 8080, baseUrlPath = ""},""), requestQueryString = fromList [], requestBody = Just ((),text/plain;charset=utf-8), requestAccept = fromList [], requestHeaders = fromList [], requestHttpVersion = HTTP/1.1, requestMethod = "POST"}) (Response {responseStatusCode = Status {statusCode = 500, statusMessage = "Internal Server Error"}, responseHeaders = fromList [("Transfer-Encoding","chunked"),("Date","Thu, 24 Nov 2022 21:04:47 GMT"),("Server","Warp/3.3.23"),("Content-Type","text/plain; charset=utf-8")], responseHttpVersion = HTTP/1.1, responseBody = "Something went wrong"}))
112+
```
113+
114+
and appends to a file called `test.txt`. We can see from the output that when a legal message is sent, the file is opened, written to, and closed. We can also see that when an illegal message is sent, the file is opened but not written to. Crucially, it is still closed even though the handler threw an exception.
Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
cabal-version: 2.2
2+
name: cookbook-managed-resource
3+
version: 0.1
4+
synopsis: Simple managed resource cookbook example
5+
homepage: http://docs.servant.dev/
6+
license: BSD-3-Clause
7+
license-file: ../../../servant/LICENSE
8+
author: Servant Contributors
9+
maintainer: [email protected]
10+
build-type: Simple
11+
tested-with: GHC==9.4.2
12+
13+
executable cookbook-managed-resource
14+
main-is: ManagedResource.lhs
15+
build-depends: base == 4.*
16+
, text >= 1.2
17+
, aeson >= 1.2
18+
, servant
19+
, servant-client
20+
, servant-server
21+
, warp >= 3.2
22+
, wai >= 3.2
23+
, http-types >= 0.12
24+
, markdown-unlit >= 0.4
25+
, http-client >= 0.5
26+
, transformers
27+
, resourcet
28+
default-language: Haskell2010
29+
ghc-options: -Wall -pgmL markdown-unlit
30+
build-tool-depends: markdown-unlit:markdown-unlit

doc/requirements.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
11
recommonmark==0.5.0
22
Sphinx==1.8.4
33
sphinx_rtd_theme>=0.4.2
4+
jinja2<3.1.0

servant-client-core/src/Servant/Client/Core/HasClient.hs

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ import Servant.API
7777
NoContentVerb, QueryFlag, QueryParam', QueryParams, Raw,
7878
ReflectMethod (..), RemoteHost, ReqBody', SBoolI, Stream,
7979
StreamBody', Summary, ToHttpApiData, ToSourceIO (..), Vault,
80-
Verb, WithNamedContext, WithStatus (..), contentType, getHeadersHList,
80+
Verb, WithNamedContext, WithResource, WithStatus (..), contentType, getHeadersHList,
8181
getResponse, toEncodedUrlPiece, toUrlPiece, NamedRoutes)
8282
import Servant.API.Generic
8383
(GenericMode(..), ToServant, ToServantApi
@@ -776,6 +776,14 @@ instance HasClient m subapi =>
776776

777777
hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy subapi) f cl
778778

779+
instance HasClient m subapi =>
780+
HasClient m (WithResource res :> subapi) where
781+
782+
type Client m (WithResource res :> subapi) = Client m subapi
783+
clientWithRoute pm Proxy = clientWithRoute pm (Proxy :: Proxy subapi)
784+
785+
hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy subapi) f cl
786+
779787
instance ( HasClient m api
780788
) => HasClient m (AuthProtect tag :> api) where
781789
type Client m (AuthProtect tag :> api)

servant-docs/golden/comprehensive.md

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -530,6 +530,24 @@
530530

531531
```
532532

533+
## GET /resource
534+
535+
### Response:
536+
537+
- Status code 200
538+
- Headers: []
539+
540+
- Supported content types are:
541+
542+
- `application/json;charset=utf-8`
543+
- `application/json`
544+
545+
- Example (`application/json;charset=utf-8`, `application/json`):
546+
547+
```javascript
548+
549+
```
550+
533551
## GET /streaming
534552

535553
### Request:

servant-docs/src/Servant/Docs/Internal.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1144,6 +1144,9 @@ instance HasDocs api => HasDocs (Vault :> api) where
11441144
instance HasDocs api => HasDocs (WithNamedContext name context api) where
11451145
docsFor Proxy = docsFor (Proxy :: Proxy api)
11461146

1147+
instance HasDocs api => HasDocs (WithResource res :> api) where
1148+
docsFor Proxy = docsFor (Proxy :: Proxy api)
1149+
11471150
instance (ToAuthInfo (BasicAuth realm usr), HasDocs api) => HasDocs (BasicAuth realm usr :> api) where
11481151
docsFor Proxy (endpoint, action) =
11491152
docsFor (Proxy :: Proxy api) (endpoint, action')

servant-foreign/src/Servant/Foreign/Internal.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -487,6 +487,13 @@ instance HasForeign lang ftype api =>
487487

488488
foreignFor lang ftype Proxy = foreignFor lang ftype (Proxy :: Proxy api)
489489

490+
instance HasForeign lang ftype api =>
491+
HasForeign lang ftype (WithResource res :> api) where
492+
493+
type Foreign ftype (WithResource res :> api) = Foreign ftype api
494+
495+
foreignFor lang ftype Proxy = foreignFor lang ftype (Proxy :: Proxy api)
496+
490497
instance HasForeign lang ftype api
491498
=> HasForeign lang ftype (HttpVersion :> api) where
492499
type Foreign ftype (HttpVersion :> api) = Foreign ftype api

servant-server/src/Servant/Server/Internal.hs

Lines changed: 40 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -35,9 +35,10 @@ module Servant.Server.Internal
3535
import Control.Monad
3636
(join, when)
3737
import Control.Monad.Trans
38-
(liftIO)
38+
(liftIO, lift)
3939
import Control.Monad.Trans.Resource
40-
(runResourceT)
40+
(runResourceT, ReleaseKey)
41+
import Data.Acquire
4142
import qualified Data.ByteString as B
4243
import qualified Data.ByteString.Builder as BB
4344
import qualified Data.ByteString.Char8 as BC8
@@ -77,7 +78,7 @@ import Servant.API
7778
QueryParam', QueryParams, Raw, ReflectMethod (reflectMethod),
7879
RemoteHost, ReqBody', SBool (..), SBoolI (..), SourceIO,
7980
Stream, StreamBody', Summary, ToSourceIO (..), Vault, Verb,
80-
WithNamedContext, NamedRoutes)
81+
WithNamedContext, WithResource, NamedRoutes)
8182
import Servant.API.Generic (GenericMode(..), ToServant, ToServantApi, GServantProduct, toServant, fromServant)
8283
import Servant.API.ContentTypes
8384
(AcceptHeader (..), AllCTRender (..), AllCTUnrender (..),
@@ -244,6 +245,42 @@ instance (KnownSymbol capture, FromHttpApiData a, Typeable a
244245
formatError = urlParseErrorFormatter $ getContextEntry (mkContextWithErrorFormatter context)
245246
hint = CaptureHint (T.pack $ symbolVal $ Proxy @capture) (typeRep (Proxy :: Proxy [a]))
246247

248+
-- | If you use 'WithResource' in one of the endpoints for your API Servant
249+
-- will provide the handler for this endpoint an argument of the specified type.
250+
-- The lifespan of this resource will be automatically managed by Servant. This
251+
-- resource will be created before the handler starts and it will be destoyed
252+
-- after it ends. A new resource is created for each request to the endpoint.
253+
254+
-- The creation and destruction are done using a 'Data.Acquire.Acquire'
255+
-- provided via server 'Context'.
256+
--
257+
-- Example
258+
--
259+
-- > type MyApi = WithResource Handle :> "writeToFile" :> Post '[JSON] NoContent
260+
-- >
261+
-- > server :: Server MyApi
262+
-- > server = writeToFile
263+
-- > where writeToFile :: (ReleaseKey, Handle) -> Handler NoContent
264+
-- > writeToFile (_, h) = hPutStrLn h "message"
265+
--
266+
-- In addition to the resource, the handler will also receive a 'ReleaseKey'
267+
-- which can be used to deallocate the resource before the end of the request
268+
-- if desired.
269+
270+
instance (HasServer api ctx, HasContextEntry ctx (Acquire a))
271+
=> HasServer (WithResource a :> api) ctx where
272+
273+
type ServerT (WithResource a :> api) m = (ReleaseKey, a) -> ServerT api m
274+
275+
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy @api) pc nt . s
276+
277+
route Proxy context d = route (Proxy @api) context (d `addParameterCheck` allocateResource)
278+
where
279+
allocateResource :: DelayedIO (ReleaseKey, a)
280+
allocateResource = DelayedIO $ lift $ allocateAcquire (getContextEntry context)
281+
282+
283+
247284
allowedMethodHead :: Method -> Request -> Bool
248285
allowedMethodHead method request = method == methodGet && requestMethod request == methodHead
249286

0 commit comments

Comments
 (0)