{-# LANGUAGE Trustworthy #-}
module Cleff.Mask
(
Mask (..)
, bracket
, bracketOnError
, bracket_
, bracketOnError_
, onError
, finally
, mask
, uninterruptibleMask
, onException
, mask_
, uninterruptibleMask_
, runMask
) where
import Cleff
import Cleff.Internal.Base
import qualified Control.Exception as Exc
data Mask :: Effect where
Mask :: ((m ~> m) -> m a) -> Mask m a
UninterruptibleMask :: ((m ~> m) -> m a) -> Mask m a
OnException :: m a -> m b -> Mask m a
makeEffect_ ''Mask
mask :: Mask :> es => ((Eff es ~> Eff es) -> Eff es a) -> Eff es a
uninterruptibleMask :: Mask :> es => ((Eff es ~> Eff es) -> Eff es a) -> Eff es a
onException :: Mask :> es
=> Eff es a
-> Eff es b
-> Eff es a
bracket :: Mask :> es
=> Eff es a
-> (a -> Eff es c)
-> (a -> Eff es b)
-> Eff es b
bracket :: Eff es a -> (a -> Eff es c) -> (a -> Eff es b) -> Eff es b
bracket Eff es a
alloc a -> Eff es c
dealloc a -> Eff es b
action = ((Eff es ~> Eff es) -> Eff es b) -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Mask :> es) =>
((Eff es ~> Eff es) -> Eff es a) -> Eff es a
mask \Eff es ~> Eff es
restore -> do
a
res <- Eff es a
alloc
b
ret <- Eff es b -> Eff es b
Eff es ~> Eff es
restore (a -> Eff es b
action a
res) Eff es b -> Eff es c -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a b.
(Mask :> es) =>
Eff es a -> Eff es b -> Eff es a
`onError` a -> Eff es c
dealloc a
res
c
_ <- Eff es c -> Eff es c
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Mask :> es) =>
Eff es a -> Eff es a
uninterruptibleMask_ (a -> Eff es c
dealloc a
res)
b -> Eff es b
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure b
ret
bracketOnError :: Mask :> es
=> Eff es a
-> (a -> Eff es c)
-> (a -> Eff es b)
-> Eff es b
bracketOnError :: Eff es a -> (a -> Eff es c) -> (a -> Eff es b) -> Eff es b
bracketOnError Eff es a
alloc a -> Eff es c
dealloc a -> Eff es b
action = ((Eff es ~> Eff es) -> Eff es b) -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Mask :> es) =>
((Eff es ~> Eff es) -> Eff es a) -> Eff es a
mask \Eff es ~> Eff es
restore -> do
a
res <- Eff es a
alloc
Eff es b -> Eff es b
Eff es ~> Eff es
restore (a -> Eff es b
action a
res) Eff es b -> Eff es c -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a b.
(Mask :> es) =>
Eff es a -> Eff es b -> Eff es a
`onError` a -> Eff es c
dealloc a
res
mask_ :: Mask :> es => Eff es a -> Eff es a
mask_ :: Eff es a -> Eff es a
mask_ Eff es a
m = ((Eff es ~> Eff es) -> Eff es a) -> Eff es a
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Mask :> es) =>
((Eff es ~> Eff es) -> Eff es a) -> Eff es a
mask \Eff es ~> Eff es
_ -> Eff es a
m
uninterruptibleMask_ :: Mask :> es => Eff es a -> Eff es a
uninterruptibleMask_ :: Eff es a -> Eff es a
uninterruptibleMask_ Eff es a
m = ((Eff es ~> Eff es) -> Eff es a) -> Eff es a
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Mask :> es) =>
((Eff es ~> Eff es) -> Eff es a) -> Eff es a
uninterruptibleMask \Eff es ~> Eff es
_ -> Eff es a
m
bracket_ :: Mask :> es => Eff es a -> Eff es c -> (a -> Eff es b) -> Eff es b
bracket_ :: Eff es a -> Eff es c -> (a -> Eff es b) -> Eff es b
bracket_ Eff es a
ma = Eff es a -> (a -> Eff es c) -> (a -> Eff es b) -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a c b.
(Mask :> es) =>
Eff es a -> (a -> Eff es c) -> (a -> Eff es b) -> Eff es b
bracket Eff es a
ma ((a -> Eff es c) -> (a -> Eff es b) -> Eff es b)
-> (Eff es c -> a -> Eff es c)
-> Eff es c
-> (a -> Eff es b)
-> Eff es b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Eff es c -> a -> Eff es c
forall a b. a -> b -> a
const
bracketOnError_ :: Mask :> es => Eff es a -> Eff es c -> (a -> Eff es b) -> Eff es b
bracketOnError_ :: Eff es a -> Eff es c -> (a -> Eff es b) -> Eff es b
bracketOnError_ Eff es a
ma = Eff es a -> (a -> Eff es c) -> (a -> Eff es b) -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a c b.
(Mask :> es) =>
Eff es a -> (a -> Eff es c) -> (a -> Eff es b) -> Eff es b
bracketOnError Eff es a
ma ((a -> Eff es c) -> (a -> Eff es b) -> Eff es b)
-> (Eff es c -> a -> Eff es c)
-> Eff es c
-> (a -> Eff es b)
-> Eff es b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Eff es c -> a -> Eff es c
forall a b. a -> b -> a
const
onError :: Mask :> es
=> Eff es a
-> Eff es b
-> Eff es a
onError :: Eff es a -> Eff es b -> Eff es a
onError Eff es a
m Eff es b
n = Eff es a
m Eff es a -> Eff es b -> Eff es a
forall (es :: [(Type -> Type) -> Type -> Type]) a b.
(Mask :> es) =>
Eff es a -> Eff es b -> Eff es a
`onException` Eff es b -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Mask :> es) =>
Eff es a -> Eff es a
uninterruptibleMask_ Eff es b
n
finally :: Mask :> es
=> Eff es a
-> Eff es b
-> Eff es a
finally :: Eff es a -> Eff es b -> Eff es a
finally Eff es a
m Eff es b
mz = (Eff es a
m Eff es a -> Eff es b -> Eff es a
forall (es :: [(Type -> Type) -> Type -> Type]) a b.
(Mask :> es) =>
Eff es a -> Eff es b -> Eff es a
`onError` Eff es b
mz) Eff es a -> Eff es b -> Eff es a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Eff es b -> Eff es b
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Mask :> es) =>
Eff es a -> Eff es a
uninterruptibleMask_ Eff es b
mz
runMask :: Eff (Mask ': es) ~> Eff es
runMask :: Eff (Mask : es) a -> Eff es a
runMask = Eff (IOE : es) a -> Eff es a
forall (es :: [(Type -> Type) -> Type -> Type]).
Eff (IOE : es) ~> Eff es
thisIsPureTrustMe (Eff (IOE : es) a -> Eff es a)
-> (Eff (Mask : es) a -> Eff (IOE : es) a)
-> Eff (Mask : es) a
-> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handler Mask (IOE : es) -> Eff (Mask : es) ~> Eff (IOE : es)
forall (e' :: (Type -> Type) -> Type -> Type)
(e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
Handler e (e' : es) -> Eff (e : es) ~> Eff (e' : es)
reinterpret \case
Mask f -> ((Eff esSend ~> IO) -> IO a) -> Eff (IOE : es) a
forall (esSend :: [(Type -> Type) -> Type -> Type])
(e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]) a.
(Handling esSend e es, IOE :> es) =>
((Eff esSend ~> IO) -> IO a) -> Eff es a
withToIO \Eff esSend ~> IO
toIO -> ((forall a. IO a -> IO a) -> IO a) -> IO a
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
Exc.mask \forall a. IO a -> IO a
restore -> Eff esSend a -> IO a
Eff esSend ~> IO
toIO (Eff esSend a -> IO a) -> Eff esSend a -> IO a
forall a b. (a -> b) -> a -> b
$ (Eff esSend ~> Eff esSend) -> Eff esSend a
f (IO a -> Eff esSend a
forall (esSend :: [(Type -> Type) -> Type -> Type])
(e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
(Handling esSend e es, IOE :> es) =>
IO ~> Eff esSend
fromIO (IO a -> Eff esSend a)
-> (Eff esSend a -> IO a) -> Eff esSend a -> Eff esSend a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> IO a
forall a. IO a -> IO a
restore (IO a -> IO a) -> (Eff esSend a -> IO a) -> Eff esSend a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Eff esSend a -> IO a
Eff esSend ~> IO
toIO)
UninterruptibleMask f -> ((Eff esSend ~> IO) -> IO a) -> Eff (IOE : es) a
forall (esSend :: [(Type -> Type) -> Type -> Type])
(e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]) a.
(Handling esSend e es, IOE :> es) =>
((Eff esSend ~> IO) -> IO a) -> Eff es a
withToIO \Eff esSend ~> IO
toIO -> ((forall a. IO a -> IO a) -> IO a) -> IO a
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
Exc.uninterruptibleMask \forall a. IO a -> IO a
restore -> Eff esSend a -> IO a
Eff esSend ~> IO
toIO (Eff esSend a -> IO a) -> Eff esSend a -> IO a
forall a b. (a -> b) -> a -> b
$ (Eff esSend ~> Eff esSend) -> Eff esSend a
f (IO a -> Eff esSend a
forall (esSend :: [(Type -> Type) -> Type -> Type])
(e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
(Handling esSend e es, IOE :> es) =>
IO ~> Eff esSend
fromIO (IO a -> Eff esSend a)
-> (Eff esSend a -> IO a) -> Eff esSend a -> Eff esSend a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> IO a
forall a. IO a -> IO a
restore (IO a -> IO a) -> (Eff esSend a -> IO a) -> Eff esSend a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Eff esSend a -> IO a
Eff esSend ~> IO
toIO)
OnException m n -> ((Eff esSend ~> IO) -> IO a) -> Eff (IOE : es) a
forall (esSend :: [(Type -> Type) -> Type -> Type])
(e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]) a.
(Handling esSend e es, IOE :> es) =>
((Eff esSend ~> IO) -> IO a) -> Eff es a
withToIO \Eff esSend ~> IO
toIO -> Eff esSend a -> IO a
Eff esSend ~> IO
toIO Eff esSend a
m IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`Exc.catch` \(SomeException
e :: Exc.SomeException) ->
IO b -> IO (Either SomeException b)
forall e a. Exception e => IO a -> IO (Either e a)
Exc.try @Exc.SomeException (Eff esSend b -> IO b
Eff esSend ~> IO
toIO Eff esSend b
n) IO (Either SomeException b) -> IO a -> IO a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> SomeException -> IO a
forall e a. Exception e => e -> IO a
Exc.throwIO SomeException
e
{-# INLINE runMask #-}