{-# options_haddock prune #-}

-- |Description: Mask Effect, Internal
module Polysemy.Conc.Effect.Mask where

import Polysemy.Conc.Effect.Scoped (Scoped, scoped)

-- |Part of an effect abstracting 'Control.Exception.mask'.
data RestoreMask :: Effect where
  Restore :: m a -> RestoreMask m a

makeSem_ ''RestoreMask

-- |Restore the previous masking state.
-- Can only be called inside of an action passed to 'mask' or 'uninterruptibleMask'.
restore ::
   r a .
  Member RestoreMask r =>
  Sem r a ->
  Sem r a

newtype MaskResource resource =
  MaskResource { forall resource. MaskResource resource -> resource
unMaskResource :: resource }

newtype UninterruptibleMaskResource resource =
  UninterruptibleMaskResource { forall resource. UninterruptibleMaskResource resource -> resource
unUninterruptibleMaskResource :: resource }

-- |The scoped masking effect.
type Mask resource =
  Scoped (MaskResource resource) RestoreMask

-- |The scoped uninterruptible masking effect.
type UninterruptibleMask resource =
  Scoped (UninterruptibleMaskResource resource) RestoreMask

-- |Mark a region as masked.
-- Uses the 'Scoped' pattern.
mask ::
   resource r .
  Member (Mask resource) r =>
  InterpreterFor RestoreMask r
mask :: forall resource (r :: [(* -> *) -> * -> *]).
Member (Mask resource) r =>
InterpreterFor RestoreMask r
mask =
  forall resource (effect :: (* -> *) -> * -> *)
       (r :: [(* -> *) -> * -> *]).
Member (Scoped resource effect) r =>
InterpreterFor effect r
scoped @(MaskResource resource)

-- |Mark a region as uninterruptibly masked.
-- Uses the 'Scoped' pattern.
uninterruptibleMask ::
   resource r .
  Member (UninterruptibleMask resource) r =>
  InterpreterFor RestoreMask r
uninterruptibleMask :: forall resource (r :: [(* -> *) -> * -> *]).
Member (UninterruptibleMask resource) r =>
InterpreterFor RestoreMask r
uninterruptibleMask =
  forall resource (effect :: (* -> *) -> * -> *)
       (r :: [(* -> *) -> * -> *]).
Member (Scoped resource effect) r =>
InterpreterFor effect r
scoped @(UninterruptibleMaskResource resource)