module Engine.Sound.Source where import RIO import Sound.OpenAL.FFI.AL qualified as AL import UnliftIO.Resource qualified as Resource import Foreign qualified class HasSource a where getSource :: a -> AL.Source instance HasSource AL.Source where getSource = id instance HasSource (a, AL.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 -- stop loaded -- for_ sources \source -> -- OpenAL.buffer source OpenAL.$= Nothing -- OpenAL.deleteObjectNames sources Foreign.withArrayLen (map getSource $ toList loaded) \num -> AL.alDeleteSources (fromIntegral num) 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 (toList -> sources) = liftIO $ Foreign.withArrayLen (map getSource sources) \num -> AL.alSourcePlayv (fromIntegral num) {-# 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 (toList -> sources) = liftIO $ Foreign.withArrayLen (map getSource sources) \num -> AL.alSourceStopv (fromIntegral num) {-# INLINE toggle #-} toggle :: (HasSource a, MonadIO m) => Bool -> a -> m () toggle active src = if active then play1 src else stop1 src