/src/Polysemy/Async.hs

https://github.com/polysemy-research/polysemy · Haskell · 141 lines · 62 code · 16 blank · 63 comment · 1 complexity · 40069ba3830dccd18f144455f88e8a46 MD5 · raw file

  1. {-# LANGUAGE TemplateHaskell #-}
  2. module Polysemy.Async
  3. ( -- * Effect
  4. Async (..)
  5. -- * Actions
  6. , async
  7. , await
  8. , cancel
  9. -- * Helpers
  10. , sequenceConcurrently
  11. -- * Interpretations
  12. , asyncToIO
  13. , asyncToIOFinal
  14. , lowerAsync
  15. ) where
  16. import qualified Control.Concurrent.Async as A
  17. import Polysemy
  18. import Polysemy.Final
  19. ------------------------------------------------------------------------------
  20. -- | An effect for spawning asynchronous computations.
  21. --
  22. -- The 'Maybe' returned by 'async' is due to the fact that we can't be sure an
  23. -- 'Polysemy.Error.Error' effect didn't fail locally.
  24. --
  25. -- @since 0.5.0.0
  26. data Async m a where
  27. Async :: m a -> Async m (A.Async (Maybe a))
  28. Await :: A.Async a -> Async m a
  29. Cancel :: A.Async a -> Async m ()
  30. makeSem ''Async
  31. ------------------------------------------------------------------------------
  32. -- | Perform a sequence of effectful actions concurrently.
  33. --
  34. -- @since 1.2.2.0
  35. sequenceConcurrently :: forall t r a. (Traversable t, Member Async r) =>
  36. t (Sem r a) -> Sem r (t (Maybe a))
  37. sequenceConcurrently t = traverse async t >>= traverse await
  38. {-# INLINABLE sequenceConcurrently #-}
  39. ------------------------------------------------------------------------------
  40. -- | A more flexible --- though less performant ---
  41. -- version of 'asyncToIOFinal'.
  42. --
  43. -- This function is capable of running 'Async' effects anywhere within an
  44. -- effect stack, without relying on 'Final' to lower it into 'IO'.
  45. -- Notably, this means that 'Polysemy.State.State' effects will be consistent
  46. -- in the presence of 'Async'.
  47. --
  48. -- 'asyncToIO' is __unsafe__ if you're using 'await' inside higher-order actions
  49. -- of other effects interpreted after 'Async'.
  50. -- See <https://github.com/polysemy-research/polysemy/issues/205 Issue #205>.
  51. --
  52. -- Prefer 'asyncToIOFinal' unless you need to run pure, stateful interpreters
  53. -- after the interpreter for 'Async'.
  54. -- (Pure interpreters are interpreters that aren't expressed in terms of
  55. -- another effect or monad; for example, 'Polysemy.State.runState'.)
  56. --
  57. -- @since 1.0.0.0
  58. asyncToIO
  59. :: Member (Embed IO) r
  60. => Sem (Async ': r) a
  61. -> Sem r a
  62. asyncToIO m = withLowerToIO $ \lower _ -> lower $
  63. interpretH
  64. ( \case
  65. Async a -> do
  66. ma <- runT a
  67. ins <- getInspectorT
  68. fa <- embed $ A.async $ lower $ asyncToIO ma
  69. pureT $ inspect ins <$> fa
  70. Await a -> pureT =<< embed (A.wait a)
  71. Cancel a -> pureT =<< embed (A.cancel a)
  72. ) m
  73. {-# INLINE asyncToIO #-}
  74. ------------------------------------------------------------------------------
  75. -- | Run an 'Async' effect in terms of 'A.async' through final 'IO'.
  76. --
  77. -- /Beware/: Effects that aren't interpreted in terms of 'IO'
  78. -- will have local state semantics in regards to 'Async' effects
  79. -- interpreted this way. See 'Final'.
  80. --
  81. -- Notably, unlike 'asyncToIO', this is not consistent with
  82. -- 'Polysemy.State.State' unless 'Polysemy.State.runStateIORef' is used.
  83. -- State that seems like it should be threaded globally throughout 'Async'
  84. -- /will not be./
  85. --
  86. -- Use 'asyncToIO' instead if you need to run
  87. -- pure, stateful interpreters after the interpreter for 'Async'.
  88. -- (Pure interpreters are interpreters that aren't expressed in terms of
  89. -- another effect or monad; for example, 'Polysemy.State.runState'.)
  90. --
  91. -- @since 1.2.0.0
  92. asyncToIOFinal :: Member (Final IO) r
  93. => Sem (Async ': r) a
  94. -> Sem r a
  95. asyncToIOFinal = interpretFinal $ \case
  96. Async m -> do
  97. ins <- getInspectorS
  98. m' <- runS m
  99. liftS $ A.async (inspect ins <$> m')
  100. Await a -> liftS (A.wait a)
  101. Cancel a -> liftS (A.cancel a)
  102. {-# INLINE asyncToIOFinal #-}
  103. ------------------------------------------------------------------------------
  104. -- | Run an 'Async' effect in terms of 'A.async'.
  105. --
  106. -- @since 1.0.0.0
  107. lowerAsync
  108. :: Member (Embed IO) r
  109. => (forall x. Sem r x -> IO x)
  110. -- ^ Strategy for lowering a 'Sem' action down to 'IO'. This is likely
  111. -- some combination of 'runM' and other interpreters composed via '.@'.
  112. -> Sem (Async ': r) a
  113. -> Sem r a
  114. lowerAsync lower m = interpretH
  115. ( \case
  116. Async a -> do
  117. ma <- runT a
  118. ins <- getInspectorT
  119. fa <- embed $ A.async $ lower $ lowerAsync lower ma
  120. pureT $ inspect ins <$> fa
  121. Await a -> pureT =<< embed (A.wait a)
  122. Cancel a -> pureT =<< embed (A.cancel a)
  123. ) m
  124. {-# INLINE lowerAsync #-}
  125. {-# DEPRECATED lowerAsync "Use 'asyncToIOFinal' instead" #-}