• Home
  • History
  • Annotate
Name Date Size #Lines LOC

..03-May-2022-

Control/Monad/Trans/H19-Mar-2020-739413

Data/H19-Mar-2020-19981

UnliftIO/H19-Mar-2020-2814

test/H19-Mar-2020-152140

ChangeLog.mdH A D07-Jun-20201.9 KiB10053

LICENSEH A D19-Mar-20201.5 KiB3124

README.mdH A D19-Mar-202012 KiB323254

Setup.lhsH A D19-Mar-2020114 84

resourcet.cabalH A D07-Jun-20201.7 KiB4743

README.md

1## resourcet
2
3Proper exception handling, especially in the presence of asynchronous
4exceptions, is a non-trivial task. But such proper handling is absolutely vital
5to any large scale application. Leaked file descriptors or database connections
6will simply not be an option when writing a popular web application, or a high
7concurrency data processing tool. So the question is, how do you deal with it?
8
9The standard approach is the bracket pattern, which appears throughout much of
10the standard libraries. `withFile` uses the bracket pattern to safely wrap up
11`openFile` and `closeFile`, guaranteeing that the file handle will be closed no
12matter what. This approach works well, and I highly recommend using it.
13
14However, there's another approach available: the [resourcet
15package](https://www.stackage.org/package/resourcet).  If the bracket pattern
16is so good, why do we need another one? The goal of this post is to answer that
17question.
18
19## What is ResourceT
20
21ResourceT is a monad transformer which creates a region of code where you can safely allocate resources. Let's write a simple example program: we'll ask the user for some input and pretend like it's a scarce resource that must be released. We'll then do something dangerous (potentially introducing a divide-by-zero error). We then want to immediately release our scarce resource and perform some long-running computation.
22
23```haskell
24#!/usr/bin/env stack
25{- stack
26     --resolver lts-9.0
27     --install-ghc
28     runghc
29     --package resourcet
30-}
31
32import Control.Monad.Trans.Resource
33import Control.Monad.IO.Class
34
35main :: IO ()
36main = runResourceT $ do
37    (releaseKey, resource) <- allocate
38        (do
39            putStrLn "Enter some number"
40            readLn)
41        (\i -> putStrLn $ "Freeing scarce resource: " ++ show i)
42    doSomethingDangerous resource
43    liftIO $ putStrLn $ "Going to release resource immediately: " ++ show resource
44    release releaseKey
45    somethingElse
46
47doSomethingDangerous :: Int -> ResourceT IO ()
48doSomethingDangerous i =
49    liftIO $ putStrLn $ "5 divided by " ++ show i ++ " is " ++ show (5 `div` i)
50
51somethingElse :: ResourceT IO ()
52somethingElse = liftIO $ putStrLn
53    "This could take a long time, don't delay releasing the resource!"
54
55```
56
57Try entering a valid value, such as 3, and then enter 0. Notice that in both cases the "Freeing scarce resource" message is printed.
58
59``` shellsession
60~ $ stack code.hs
61Enter some number
623
635 divided by 3 is 1
64Going to release resource immediately: 3
65Freeing scarce resource: 3
66This could take a long time, don't delay releasing the resource!
67
68~ $ stack code.hs
69Enter some number
700
715 divided by 0 is Freeing scarce resource: 0
72code.hs: divide by zero
73```
74
75And by using `release` before `somethingElse`, we guarantee that the resource is freed *before* running the potentially long process.
76
77In this specific case, we could easily represent our code in terms of bracket with a little refactoring.
78
79```haskell
80import Control.Exception (bracket)
81
82main :: IO ()
83main = do
84    bracket
85        (do
86            putStrLn "Enter some number"
87            readLn)
88        (\i -> putStrLn $ "Freeing scarce resource: " ++ show i)
89        doSomethingDangerous
90    somethingElse
91
92doSomethingDangerous :: Int -> IO ()
93doSomethingDangerous i =
94    putStrLn $ "5 divided by " ++ show i ++ " is " ++ show (5 `div` i)
95
96somethingElse :: IO ()
97somethingElse = putStrLn
98    "This could take a long time, don't delay releasing the resource!"
99```
100
101In fact, the `bracket` version is cleaner than the resourcet version. If so, why bother with resourcet at all? Let's build up to the more complicated cases.
102
103## bracket in terms of ResourceT
104
105The first thing to demonstrate is that `ResourceT` is strictly more powerful than `bracket`, in the sense that:
106
1071. `bracket` can be implemented in terms of `ResourceT`.
1082. `ResourceT` cannot be implemented in terms of `bracket`.
109
110The first one is pretty easy to demonstrate:
111
112```haskell
113#!/usr/bin/env stack
114{- stack
115     --resolver lts-9.0
116     --install-ghc
117     runghc
118     --package resourcet
119-}
120
121{-# LANGUAGE FlexibleContexts #-}
122
123import Control.Monad.Trans.Resource
124import Control.Monad.Trans.Class
125import Control.Monad.IO.Class (MonadIO)
126
127bracket ::
128  (MonadThrow m, MonadBaseControl IO m,
129   MonadIO m) =>
130  IO t -> (t -> IO ()) -> (t -> m a) -> m a
131bracket alloc free inside = runResourceT $ do
132  (releaseKey, resource) <- allocate alloc free
133  lift $ inside resource
134
135main :: IO ()
136main = bracket
137       (putStrLn "Allocating" >> return 5)
138       (\i -> putStrLn $ "Freeing: " ++ show i)
139       (\i -> putStrLn $ "Using: " ++ show i)
140```
141
142Now let's analyze why the second statement is true.
143
144## What ResourceT adds
145
146The `bracket` pattern is designed with nested resource allocations. For example, consider the following program which copies data from one file to another. We'll open up the source file using `withFile`, and then nest within it another `withFile` to open the destination file, and finally do the copying with both file handles.
147
148```haskell
149{-# START_FILE main.hs #-}
150import System.IO
151import qualified Data.ByteString as S
152
153main = do
154    withFile "input.txt" ReadMode $ \input ->
155      withFile "output.txt" WriteMode $ \output -> do
156        bs <- S.hGetContents input
157        S.hPutStr output bs
158    S.readFile "output.txt" >>= S.putStr
159{-# START_FILE input.txt #-}
160This is the input file.
161```
162
163But now, let's tweak this a bit. Instead of reading from a single file, we want to read from two files and concatenate them. We could just have three nested `withFile` calls, but that would be inefficient: we'd have two `Handle`s open for reading at once, even though we'll only ever need one. We could restructure our program a bit instead: put the `withFile` for the output file on the outside, and then have two calls to `withFile` for the input files on the inside.
164
165But consider a more complicated example. Instead of just a single destination file, let's say we want to break up our input stream into chunks of, say, 50 bytes each, and write each chunk to successive output files. We now need to __interleave__ allocations and freeings of both the source and destination files, and we cannot statically know exactly how the interleaving will look, since we don't know the size of the files at compile time.
166
167This is the kind of situation that `resourcet` solves well (we'll demonstrate in the next section). As an extension of this, we can write library functions which allow user code to request arbitrary resource allocations, and we can guarantee that they will be cleaned up. A prime example of this is in WAI (Web Application Interface). The user application may wish to allocate some scarce resources (such as database statements) and use them in the generation of the response body. Using `ResourceT`, the web server can guarantee that these resources will be cleaned up.
168
169
170## Interleaving with conduit
171
172Let's demonstrate the interleaving example described above. To simplify the code, we'll use the conduit package for the actual chunking implementation. Notice when you run the program that there are never more than two file handles open at the same time.
173
174```haskell
175#!/usr/bin/env stack
176{- stack
177     --resolver lts-10.0
178     --install-ghc
179     runghc
180     --package resourcet
181     --package conduit
182     --package directory
183-}
184
185{-#LANGUAGE FlexibleContexts#-}
186{-#LANGUAGE RankNTypes#-}
187
188import           Control.Monad.IO.Class (liftIO)
189import           Control.Monad.Trans.Resource (runResourceT, ResourceT, MonadResource)
190import           Data.Conduit           (Producer, Consumer,addCleanup, (.|))
191import           Conduit (runConduitRes)
192import           Data.Conduit.Binary    (isolate, sinkFile, sourceFile)
193import           Data.Conduit.List      (peek)
194import           Data.Conduit.Zlib      (gzip)
195import           System.Directory       (createDirectoryIfMissing)
196import qualified Data.ByteString as B
197
198-- show all of the files we'll read from
199infiles :: [String]
200infiles = map (\i -> "input/" ++ show i ++ ".bin") [1..10]
201
202-- Generate a filename to write to
203outfile :: Int -> String
204outfile i = "output/" ++ show i ++ ".gz"
205
206-- Modified sourceFile and sinkFile that print when they are opening and
207-- closing file handles, to demonstrate interleaved allocation.
208sourceFileTrace :: (MonadResource m) => FilePath -> Producer m B.ByteString
209sourceFileTrace fp = do
210    liftIO $ putStrLn $ "Opening: " ++ fp
211    addCleanup (const $ liftIO $ putStrLn $ "Closing: " ++ fp) (sourceFile fp)
212
213sinkFileTrace :: (MonadResource m) => FilePath -> Consumer B.ByteString m ()
214sinkFileTrace fp = do
215    liftIO $ putStrLn $ "Opening: " ++ fp
216    addCleanup (const $ liftIO $ putStrLn $ "Closing: " ++ fp) (sinkFile fp)
217
218-- Monad instance of Producer allows us to simply mapM_ to create a single Source
219-- for reading all of the files sequentially.
220source :: (MonadResource m) => Producer m B.ByteString
221source = mapM_ sourceFileTrace infiles
222
223-- The Sink is a bit more complicated: we keep reading 30kb chunks of data into
224-- new files. We then use peek to check if there is any data left in the
225-- stream. If there is, we continue the process.
226sink :: (MonadResource m) => Consumer B.ByteString m ()
227sink =
228    loop 1
229  where
230    loop i = do
231        isolate (30 * 1024) .| sinkFileTrace (outfile i)
232        mx <- peek
233        case mx of
234            Nothing -> return ()
235            Just _ -> loop (i + 1)
236
237fillRandom :: FilePath -> IO ()
238fillRandom fp = runConduitRes $
239                sourceFile "/dev/urandom"
240                .| isolate (50 * 1024)
241                .| sinkFile fp
242
243-- Putting it all together is trivial. ResourceT guarantees we have exception
244-- safety.
245transform :: IO ()
246transform = runConduitRes $ source .| gzip .| sink
247-- /show
248
249-- Just some setup for running our test.
250main :: IO ()
251main = do
252    createDirectoryIfMissing True "input"
253    createDirectoryIfMissing True "output"
254    mapM_ fillRandom infiles
255    transform
256```
257
258## resourcet is not conduit
259
260resourcet was originally created in the process of writing the conduit package.
261As a result, many people have the impression that these two concepts are
262intrinsically linked. In fact, this is not true: each can be used separately
263from the other. The canonical demonstration of resourcet combined with conduit
264is the file copy function:
265
266```haskell
267#!/usr/bin/env stack
268{- stack
269     --resolver lts-10.0
270     --install-ghc
271     runghc
272     --package conduit
273     --package resourcet
274-}
275
276{-#LANGUAGE FlexibleContexts#-}
277
278import Data.Conduit
279import Data.Conduit.Binary
280
281fileCopy :: FilePath -> FilePath -> IO ()
282fileCopy src dst = runConduitRes $ sourceFile src .| sinkFile dst
283
284main :: IO ()
285main = do
286  writeFile "input.txt" "Hello"
287  fileCopy "input.txt" "output.txt"
288  readFile "output.txt" >>= putStrLn
289```
290
291However, since this function does not actually use any of ResourceT's added functionality, it can easily be implemented with the bracket pattern instead:
292
293```haskell
294#!/usr/bin/env stack
295{- stack
296     --resolver lts-10.0
297     --install-ghc
298     runghc
299     --package conduit
300-}
301
302import Data.Conduit
303import Data.Conduit.Binary
304import System.IO
305
306fileCopy :: FilePath -> FilePath -> IO ()
307fileCopy src dst = withFile src ReadMode $ \srcH ->
308                   withFile dst WriteMode $ \dstH ->
309                   sourceHandle srcH $$ sinkHandle dstH
310
311main :: IO ()
312main = do
313    writeFile "input.txt" "Hello"
314    fileCopy "input.txt" "output.txt"
315    readFile "output.txt" >>= putStrLn
316```
317
318Likewise, resourcet can be freely used for more flexible resource management without touching conduit. In other words, these two libraries are completely orthogonal and, while they complement each other nicely, can certainly be used separately.
319
320## Conclusion
321
322ResourceT provides you with a flexible means of allocating resources in an exception safe manner. Its main advantage over the simpler bracket pattern is that it allows interleaving of allocations, allowing for more complicated programs to be created efficiently. If your needs are simple, stick with bracket. If you have need of something more complex, resourcet may be your answer. For understanding how it works under the hood, refer [here](https://www.fpcomplete.com/blog/2017/06/understanding-resourcet).
323