mirror of
https://github.com/sayo-hs/heftia.git
synced 2024-11-23 02:42:06 +03:00
[fix] Generalize runUnliftIO
to use any monad that is an instance of MonadUnliftIO
.
This commit is contained in:
parent
7e5fb2fdde
commit
ddde1044d4
@ -37,3 +37,4 @@
|
||||
* Renamed `Control.Monad.Hefty.Writer.listen` -> `intercept`
|
||||
|
||||
* Reexported `Data.Effect.*` from the interpreters module `Control.Monad.Hefty.*`.
|
||||
* Generalized `runUnliftIO` to use any monad that is an instance of `MonadUnliftIO`.
|
||||
|
@ -16,12 +16,15 @@ where
|
||||
|
||||
import Control.Monad.Hefty (Eff, interpretH, runEff, send0, type (~>))
|
||||
import Data.Effect.Unlift
|
||||
import UnliftIO (MonadUnliftIO)
|
||||
import UnliftIO qualified as IO
|
||||
|
||||
runUnliftBase :: forall b. (Monad b) => Eff '[UnliftBase b] '[b] ~> b
|
||||
runUnliftBase =
|
||||
runEff . interpretH \(WithRunInBase f) ->
|
||||
send0 $ f runEff
|
||||
|
||||
runUnliftIO :: Eff '[UnliftIO] '[IO] ~> IO
|
||||
runUnliftIO = runUnliftBase
|
||||
{-# INLINE runUnliftIO #-}
|
||||
runUnliftIO :: (MonadUnliftIO m) => Eff '[UnliftIO] '[m] ~> m
|
||||
runUnliftIO =
|
||||
runEff . interpretH \(WithRunInBase f) ->
|
||||
send0 $ IO.withRunInIO \run -> f $ run . runEff
|
||||
|
Loading…
Reference in New Issue
Block a user