{-# options_haddock prune #-}

-- |Description: Events/Consume Effects, Internal
module Polysemy.Conc.Effect.Events where

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

-- |Marker for the 'Scoped' resource for 'Events'.
newtype EventResource resource =
  EventResource { forall resource. EventResource resource -> resource
unEventToken :: resource }
  deriving stock (EventResource resource -> EventResource resource -> Bool
(EventResource resource -> EventResource resource -> Bool)
-> (EventResource resource -> EventResource resource -> Bool)
-> Eq (EventResource resource)
forall resource.
Eq resource =>
EventResource resource -> EventResource resource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventResource resource -> EventResource resource -> Bool
$c/= :: forall resource.
Eq resource =>
EventResource resource -> EventResource resource -> Bool
== :: EventResource resource -> EventResource resource -> Bool
$c== :: forall resource.
Eq resource =>
EventResource resource -> EventResource resource -> Bool
Eq, Int -> EventResource resource -> ShowS
[EventResource resource] -> ShowS
EventResource resource -> String
(Int -> EventResource resource -> ShowS)
-> (EventResource resource -> String)
-> ([EventResource resource] -> ShowS)
-> Show (EventResource resource)
forall resource.
Show resource =>
Int -> EventResource resource -> ShowS
forall resource. Show resource => [EventResource resource] -> ShowS
forall resource. Show resource => EventResource resource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventResource resource] -> ShowS
$cshowList :: forall resource. Show resource => [EventResource resource] -> ShowS
show :: EventResource resource -> String
$cshow :: forall resource. Show resource => EventResource resource -> String
showsPrec :: Int -> EventResource resource -> ShowS
$cshowsPrec :: forall resource.
Show resource =>
Int -> EventResource resource -> ShowS
Show, (forall x.
 EventResource resource -> Rep (EventResource resource) x)
-> (forall x.
    Rep (EventResource resource) x -> EventResource resource)
-> Generic (EventResource resource)
forall x. Rep (EventResource resource) x -> EventResource resource
forall x. EventResource resource -> Rep (EventResource resource) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall resource x.
Rep (EventResource resource) x -> EventResource resource
forall resource x.
EventResource resource -> Rep (EventResource resource) x
$cto :: forall resource x.
Rep (EventResource resource) x -> EventResource resource
$cfrom :: forall resource x.
EventResource resource -> Rep (EventResource resource) x
Generic)

-- |An event publisher that can be consumed from multiple threads.
data Events (resource :: Type) (e :: Type) :: Effect where
  Publish :: e -> Events resource e m ()

makeSem_ ''Events

-- |Publish one event.
publish ::
   e resource r .
  Member (Events resource e) r =>
  e ->
  Sem r ()

-- |Consume events emitted by 'Events'.
data Consume (e :: Type) :: Effect where
  Consume :: Consume e m e

makeSem_ ''Consume

-- |Consume one event emitted by 'Events'.
consume ::
   e r .
  Member (Consume e) r =>
  Sem r e

-- |Create a new scope for 'Events', causing the nested program to get its own copy of the event stream.
-- To be used with 'Polysemy.Conc.interpretEventsChan'.
subscribe ::
   e resource r .
  Member (Scoped (EventResource resource) (Consume e)) r =>
  InterpreterFor (Consume e) r
subscribe :: forall e resource (r :: [(* -> *) -> * -> *]).
Member (Scoped (EventResource resource) (Consume e)) r =>
InterpreterFor (Consume e) r
subscribe =
  forall resource (effect :: (* -> *) -> * -> *)
       (r :: [(* -> *) -> * -> *]).
Member (Scoped resource effect) r =>
InterpreterFor effect r
scoped @(EventResource resource)