module TheatreDev.Tell where import Data.Vector qualified as Vector import TheatreDev.Prelude type Tell a = a -> STM () either :: Tell a -> Tell a -> Tell a either :: forall a. Tell a -> Tell a -> Tell a either Tell a lTell Tell a rTell a msg = Tell a lTell a msg forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> Tell a rTell a msg both :: Tell a -> Tell a -> Tell a both :: forall a. Tell a -> Tell a -> Tell a both Tell a lTell Tell a rTell a msg = Tell a lTell a msg forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> Tell a rTell a msg one :: [Tell a] -> Tell a one :: forall a. [Tell a] -> Tell a one [Tell a] tells a msg = forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum forall a b. (a -> b) -> a -> b $ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\Tell a tell -> Tell a tell a msg) [Tell a] tells all :: [Tell a] -> Tell a all :: forall a. [Tell a] -> Tell a all [Tell a] tells a msg = forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, Applicative f) => (a -> f b) -> t a -> f () traverse_ (\Tell a tell -> Tell a tell a msg) [Tell a] tells byKeyHashOneOf :: (a -> Int) -> [Tell a] -> Tell a byKeyHashOneOf :: forall a. (a -> Int) -> [Tell a] -> Tell a byKeyHashOneOf a -> Int proj [Tell a] tells = let vector :: Vector (Tell a) vector = forall a. [a] -> Vector a Vector.fromList [Tell a] tells vectorLength :: Int vectorLength = forall a. Vector a -> Int Vector.length Vector (Tell a) vector in case Int vectorLength of Int 0 -> forall a b. a -> b -> a const (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) Int _ -> \a msg -> let index :: Int index = forall a. Integral a => a -> a -> a mod (a -> Int proj a msg) Int vectorLength tellAtIndex :: Tell a tellAtIndex = forall a. Vector a -> Int -> a Vector.unsafeIndex Vector (Tell a) vector Int index in Tell a tellAtIndex a msg