module Engine.Sound.Source where import RIO import Sound.OpenAL qualified as OpenAL import UnliftIO.Resource qualified as Resource class HasSource a where getSource :: a -> OpenAL.Source instance HasSource OpenAL.Source where getSource = id instance HasSource (a, OpenAL.Source) where getSource = snd allocateCollectionWith :: ( Resource.MonadResource m , Traversable t , HasSource o ) => (i -> m o) -> t i -> m (Resource.ReleaseKey, t o) allocateCollectionWith action collection = do loaded <- traverse action collection key <- Resource.register do let sources = map getSource $ toList loaded OpenAL.stop sources for_ sources \source -> OpenAL.buffer source OpenAL.$= Nothing OpenAL.deleteObjectNames sources pure (key, loaded) {-# INLINE play1 #-} play1 :: (HasSource a, MonadIO m) => a -> m () play1 src = play [src] {-# INLINE play #-} play :: (Foldable t, HasSource a, MonadIO m) => t a -> m () play = OpenAL.play . map getSource . toList {-# INLINE stop1 #-} stop1 :: (HasSource a, MonadIO m) => a -> m () stop1 src = stop [src] {-# INLINE stop #-} stop :: (Foldable t, HasSource a, MonadIO m) => t a -> m () stop = OpenAL.stop . map getSource . toList {-# INLINE toggle #-} toggle :: (HasSource a, MonadIO m) => Bool -> a -> m () toggle active src = if active then OpenAL.play srcs else OpenAL.stop srcs where srcs = [getSource src]