module STM.Hub (
HubLength,
Hub,
hub,
hubMsg,
hubEmpty,
Source,
source,
sourceMsg
)where
import Lawless
import STM.Base
newtype HubLength = HubLength Word64
deriving (Eq, Ord, Show, Bounded, Enum, Num, Integral, Real)
newtype Hub a = Hub {unHub ∷ TBChan a}
hub ∷ MonadBase IO m ⇒ HubLength → m (Hub a)
hub l = liftBase $ Hub <$> (newTBChanIO $ fromIntegral l)
hubMsg ∷ MonadBase IO m ⇒ (Hub a) → (m a)
hubMsg = atomically ∘ readTBChan ∘ unHub
hubEmpty ∷ MonadBase IO m ⇒ (Hub a) → (m Bool)
hubEmpty = atomically ∘ isEmptyTBChan ∘ unHub
newtype Source a = Source {unSource ∷ TBChan a}
source ∷ Getter (Hub a) (Source a)
source = to $ Source ∘ unHub
sourceMsg ∷ MonadBase IO m ⇒ Source a → a → m ()
sourceMsg s = atomically ∘ writeTBChan (unSource s)