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

..03-May-2022-

bench/H24-Jan-2021-137128

cbits/H24-Jan-2021-11570

src/H24-Jan-2021-5,9542,915

test/H24-Jan-2021-672560

ChangeLog.mdH A D24-Jan-20211.8 KiB10260

LICENSEH A D24-Jan-20211 KiB2117

README.mdH A D24-Jan-202114.8 KiB390304

Setup.hsH A D24-Jan-202146 32

unliftio.cabalH A D24-Jan-20213.3 KiB154148

README.md

1# unliftio
2
3![Tests](https://github.com/fpco/unliftio/workflows/Tests/badge.svg)
4
5
6Provides the core `MonadUnliftIO` typeclass, a number of common
7instances, and a collection of common functions working with it.  Not
8sure what the `MonadUnliftIO` typeclass is all about? Read on!
9
10__NOTE__ This library is young, and will likely undergo some serious changes
11over time. It's also very lightly tested. That said: the core concept of
12`MonadUnliftIO` has been refined for years and is pretty solid, and even though
13the code here is lightly tested, the vast majority of it is simply apply
14`withUnliftIO` to existing functionality. Caveat emptor and all that.
15
16__NOTE__ The `UnliftIO.Exception` module in this library changes the semantics of asynchronous exceptions to be in the style of the `safe-exceptions` package, which is orthogonal to the "unlifting" concept. While this change is an improvment in most cases, it means that `UnliftIO.Exception` is not always a drop-in replacement for `Control.Exception` in advanced exception handling code. See [Async exception safety](#async-exception-safety) for details.
17
18## Quickstart
19
20* Replace imports like `Control.Exception` with
21  `UnliftIO.Exception`. Yay, your `catch` and `finally` are more
22  powerful and safer (see [Async exception safety](#async-exception-safety))!
23* Similar with `Control.Concurrent.Async` with `UnliftIO.Async`
24* Or go all in and import `UnliftIO`
25* Naming conflicts: let `unliftio` win
26* Drop the deps on `monad-control`, `lifted-base`, and `exceptions`
27* Compilation failures? You may have just avoided subtle runtime bugs
28
29Sound like magic? It's not. Keep reading!
30
31## Unlifting in 2 minutes
32
33Let's say I have a function:
34
35```haskell
36readFile :: FilePath -> IO ByteString
37```
38
39But I'm writing code inside a function that uses `ReaderT Env IO`, not
40just plain `IO`. How can I call my `readFile` function in that
41context? One way is to manually unwrap the `ReaderT` data constructor:
42
43```haskell
44myReadFile :: FilePath -> ReaderT Env IO ByteString
45myReadFile fp = ReaderT $ \_env -> readFile fp
46```
47
48But having to do this regularly is tedious, and ties our code to a
49specific monad transformer stack. Instead, many of us would use
50`MonadIO`:
51
52```haskell
53myReadFile :: MonadIO m => FilePath -> m ByteString
54myReadFile = liftIO . readFile
55```
56
57But now let's play with a different function:
58
59```haskell
60withBinaryFile :: FilePath -> IOMode -> (Handle -> IO a) -> IO a
61```
62
63We want a function with signature:
64
65```haskell
66myWithBinaryFile
67    :: FilePath
68    -> IOMode
69    -> (Handle -> ReaderT Env IO a)
70    -> ReaderT Env IO a
71```
72
73If I squint hard enough, I can accomplish this directly with the
74`ReaderT` constructor via:
75
76```haskell
77myWithBinaryFile fp mode inner =
78  ReaderT $ \env -> withBinaryFile
79    fp
80    mode
81    (\h -> runReaderT (inner h) env)
82```
83
84I dare you to try and accomplish this with `MonadIO` and
85`liftIO`. It simply can't be done. (If you're looking for the
86technical reason, it's because `IO` appears in
87[negative/argument position](https://www.fpcomplete.com/blog/2016/11/covariance-contravariance)
88in `withBinaryFile`.)
89
90However, with `MonadUnliftIO`, this is possible:
91
92```haskell
93import Control.Monad.IO.Unlift
94
95myWithBinaryFile
96    :: MonadUnliftIO m
97    => FilePath
98    -> IOMode
99    -> (Handle -> m a)
100    -> m a
101myWithBinaryFile fp mode inner =
102  withRunInIO $ \runInIO ->
103  withBinaryFile
104    fp
105    mode
106    (\h -> runInIO (inner h))
107```
108
109That's it, you now know the entire basis of this library.
110
111## How common is this problem?
112
113This pops up in a number of places. Some examples:
114
115* Proper exception handling, with functions like `bracket`, `catch`,
116  and `finally`
117* Working with `MVar`s via `modifyMVar` and similar
118* Using the `timeout` function
119* Installing callback handlers (e.g., do you want to do
120  [logging](https://www.stackage.org/package/monad-logger) in a signal
121  handler?).
122
123This also pops up when working with libraries which are monomorphic on
124`IO`, even if they could be written more extensibly.
125
126## Examples
127
128Reading through the codebase here is likely the best example to see
129how to use `MonadUnliftIO` in practice. And for many cases, you can
130simply add the `MonadUnliftIO` constraint and then use the
131pre-unlifted versions of functions (like
132`UnliftIO.Exception.catch`). But ultimately, you'll probably want to
133use the typeclass directly. The type class has only one method --
134`withRunInIO`:
135
136```haskell
137class MonadIO m => MonadUnliftIO m where
138  withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b
139```
140
141`withRunInIO` provides a function to run arbitrary computations in `m`
142in `IO`. Thus the "unlift": it's like `liftIO`, but the other way around.
143
144Here are some sample typeclass instances:
145
146```haskell
147instance MonadUnliftIO IO where
148  withRunInIO inner = inner id
149
150instance MonadUnliftIO m => MonadUnliftIO (ReaderT r m) where
151  withRunInIO inner =
152    ReaderT $ \r ->
153    withRunInIO $ \run ->
154    inner (run . flip runReaderT r)
155
156instance MonadUnliftIO m => MonadUnliftIO (IdentityT m) where
157  withRunInIO inner =
158    IdentityT $
159    withRunInIO $ \run ->
160    inner (run . runIdentityT)
161```
162
163Note that:
164
165* The `IO` instance does not actually do any lifting or unlifting, and
166  therefore it can use `id`
167* `IdentityT` is essentially just wrapping/unwrapping its data
168  constructor, and then recursively calling `withRunInIO` on the
169  underlying monad.
170* `ReaderT` is just like `IdentityT`, but it captures the reader
171  environment when starting.
172
173We can use `withRunInIO` to unlift a function:
174
175```haskell
176timeout :: MonadUnliftIO m => Int -> m a -> m (Maybe a)
177timeout x y = withRunInIO $ \run -> System.Timeout.timeout x $ run y
178```
179
180This is a common pattern: use `withRunInIO` to capture a run function,
181and then call the original function with the user-supplied arguments,
182applying `run` as necessary. `withRunInIO` takes care of invoking
183`unliftIO` for us.
184
185We can also use the run function with different types due to
186`withRunInIO` being higher-rank polymorphic:
187
188```haskell
189race :: MonadUnliftIO m => m a -> m b -> m (Either a b)
190race a b = withRunInIO $ \run -> A.race (run a) (run b)
191```
192
193And finally, a more complex usage, when unlifting the `mask`
194function. This function needs to unlift values to be passed into the
195`restore` function, and then `liftIO` the result of the `restore`
196function.
197
198```haskell
199mask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b
200mask f = withRunInIO $ \run -> Control.Exception.mask $ \restore ->
201  run $ f $ liftIO . restore . run
202```
203
204## Limitations
205
206Not all monads which can be an instance of `MonadIO` can be instances
207of `MonadUnliftIO`, due to the `MonadUnliftIO` laws (described in the
208Haddocks for the typeclass). This prevents instances for a number of
209classes of transformers:
210
211* Transformers using continuations (e.g., `ContT`, `ConduitM`, `Pipe`)
212* Transformers with some monadic state (e.g., `StateT`, `WriterT`)
213* Transformers with multiple exit points (e.g., `ExceptT` and its ilk)
214
215In fact, there are two specific classes of transformers that this
216approach does work for:
217
218* Transformers with no context at all (e.g., `IdentityT`, `NoLoggingT`)
219* Transformers with a context but no state (e.g., `ReaderT`, `LoggingT`)
220
221This may sound restrictive, but this restriction is fully
222intentional. Trying to unlift actions in stateful monads leads to
223unpredictable behavior. For a long and exhaustive example of this, see
224[A Tale of Two Brackets](https://www.fpcomplete.com/blog/2017/06/tale-of-two-brackets),
225which was a large motivation for writing this library.
226
227## Comparison to other approaches
228
229You may be thinking "Haven't I seen a way to do `catch` in `StateT`?"
230You almost certainly have. Let's compare this approach with
231alternatives. (For an older but more thorough rundown of the options,
232see
233[Exceptions and monad transformers](http://www.yesodweb.com/blog/2014/06/exceptions-transformers).)
234
235There are really two approaches to this problem:
236
237* Use a set of typeclasses for the specific functionality we care
238  about. This is the approach taken by the `exceptions` package with
239  `MonadThrow`, `MonadCatch`, and `MonadMask`. (Earlier approaches
240  include `MonadCatchIO-mtl` and `MonadCatchIO-transformers`.)
241* Define a generic typeclass that allows any control structure to be
242  unlifted. This is the approach taken by the `monad-control`
243  package. (Earlier approaches include `monad-peel` and `neither`.)
244
245The first style gives extra functionality in allowing instances that
246have nothing to do with runtime exceptions (e.g., a `MonadCatch`
247instance for `Either`). This is arguably a good thing. The second
248style gives extra functionality in allowing more operations to be
249unlifted (like threading primitives, not supported by the `exceptions`
250package).
251
252Another distinction within the generic typeclass family is whether we
253unlift to just `IO`, or to arbitrary base monads. For those familiar,
254this is the distinction between the `MonadIO` and `MonadBase`
255typeclasses.
256
257This package's main objection to all of the above approaches is that
258they work for too many monads, and provide difficult-to-predict
259behavior for a number of them (arguably: plain wrong behavior). For
260example, in `lifted-base` (built on top of `monad-control`), the
261`finally` operation will discard mutated state coming from the cleanup
262action, which is usually not what people expect. `exceptions` has
263_different_ behavior here, which is arguably better. But we're arguing
264here that we should disallow all such ambiguity at the type level.
265
266So comparing to other approaches:
267
268### monad-unlift
269
270Throwing this one out there now: the `monad-unlift` library is built
271on top of `monad-control`, and uses fairly sophisticated type level
272features to restrict it to only the safe subset of monads. The same
273approach is taken by `Control.Concurrent.Async.Lifted.Safe` in the
274`lifted-async` package. Two problems with this:
275
276* The complicated type level functionality can confuse GHC in some
277  cases, making it difficult to get code to compile.
278* We don't have an ecosystem of functions like `lifted-base` built on
279  top of it, making it likely people will revert to the less safe
280  cousin functions.
281
282### monad-control
283
284The main contention until now is that unlifting in a transformer like
285`StateT` is unsafe. This is not universally true: if only one action
286is being unlifted, no ambiguity exists. So, for example, `try :: IO a
287-> IO (Either e a)` can safely be unlifted in `StateT`, while `finally
288:: IO a -> IO b -> IO a` cannot.
289
290`monad-control` allows us to unlift both styles. In theory, we could
291write a variant of `lifted-base` that never does state discards, and
292let `try` be more general than `finally`. In other words, this is an
293advantage of `monad-control` over `MonadUnliftIO`. We've avoided
294providing any such extra typeclass in this package though, for two
295reasons:
296
297* `MonadUnliftIO` is a simple typeclass, easy to explain. We don't
298  want to complicated matters (`MonadBaseControl` is a notoriously
299  difficult to understand typeclass). This simplicity
300  is captured by the laws for `MonadUnliftIO`, which make the
301  behavior of the run functions close to that of the already familiar
302  `lift` and `liftIO`.
303* Having this kind of split would be confusing in user code, when
304  suddenly `finally` is not available to us. We would rather encourage
305  [good practices](https://www.fpcomplete.com/blog/2017/06/readert-design-pattern)
306  from the beginning.
307
308Another distinction is that `monad-control` uses the `MonadBase`
309style, allowing unlifting to arbitrary base monads. In this package,
310we've elected to go with `MonadIO` style. This limits what we can do
311(e.g., no unlifting to `STM`), but we went this way because:
312
313* In practice, we've found that the vast majority of cases are dealing
314  with `IO`
315* The split in the ecosystem between constraints like `MonadBase IO`
316  and `MonadIO` leads to significant confusion, and `MonadIO` is by
317  far the more common constraints (with the typeclass existing in
318  `base`)
319
320### exceptions
321
322One thing we lose by leaving the `exceptions` approach is the ability
323to model both pure and side-effecting (via `IO`) monads with a single
324paradigm. For example, it can be pretty convenient to have
325`MonadThrow` constraints for parsing functions, which will either
326return an `Either` value or throw a runtime exception. That said,
327there are detractors of that approach:
328
329* You lose type information about which exception was thrown
330* There is ambiguity about _how_ the exception was returned in a
331  constraint like `(MonadIO m, MonadThrow m`)
332
333The latter could be addressed by defining a law such as `throwM =
334liftIO . throwIO`. However, we've decided in this library to go the
335route of encouraging `Either` return values for pure functions, and
336using runtime exceptions in `IO` otherwise. (You're of course free to
337also return `IO (Either e a)`.)
338
339By losing `MonadCatch`, we lose the ability to define a generic way to
340catch exceptions in continuation based monads (such as
341`ConduitM`). Our argument here is that those monads can freely provide
342their own catching functions. And in practice, long before the
343`MonadCatch` typeclass existed, `conduit` provided a `catchC`
344function.
345
346In exchange for the `MonadThrow` typeclass, we provide helper
347functions to convert `Either` values to runtime exceptions in this
348package. And the `MonadMask` typeclass is now replaced fully by
349`MonadUnliftIO`, which like the `monad-control` case limits which
350monads we can be working with.
351
352## Async exception safety
353
354The [`safe-exceptions`](https://hackage.haskell.org/package/safe-exceptions)
355package builds on top of the `exceptions`
356package and provides intelligent behavior for dealing with
357asynchronous exceptions, a common pitfall. This library provides a set
358of exception handling functions with the same async exception behavior
359as that library. You can consider this library a drop-in replacement
360for `safe-exceptions`. In the future, we may reimplement
361`safe-exceptions` to use `MonadUnliftIO` instead of `MonadCatch` and
362`MonadMask`.
363
364## Package split
365
366The `unliftio-core` package provides just the typeclass with minimal
367dependencies (just `base` and `transformers`). If you're writing a
368library, we recommend depending on that package to provide your
369instances. The `unliftio` package is a "batteries loaded" library
370providing a plethora of pre-unlifted helper functions. It's a good
371choice for importing, or even for use in a custom prelude.
372
373## Orphans
374
375The `unliftio` package currently provides orphan instances for types
376from the `resourcet` and `monad-logger` packages. This is not intended
377as a long-term solution; once `unliftio` is deemed more stable, the
378plan is to move those instances into the respective libraries and
379remove the dependency on them here.
380
381If there are other temporary orphans that should be added, please
382bring it up in the issue tracker or send a PR, but we'll need to be
383selective about adding dependencies.
384
385## Future questions
386
387* Should we extend the set of functions exposed in `UnliftIO.IO` to include
388  things like `hSeek`?
389* Are there other libraries that deserve to be unlifted here?
390