module Engine.DataRecycler where import RIO import Control.Concurrent.Chan.Unagi qualified as Unagi data DataRecycler a = DataRecycler { drDump :: DumpResource a {- ^ Filled with resources which aren't destroyed after finishing a frame, but instead are used by another frame which executes after that one is retired, (taken from ghRecycleOut) Make sure not to pass any resources which were created with a frame-only scope however! -} , drWait :: WaitResource a -- ^ The resources of prior frames waiting to be taken } type DumpResource a = a -> IO () type WaitResource a = IO (Either (IO a) a) new :: MonadIO m => m (DataRecycler a) new = do (recycleWrite, recycleRead) <- liftIO Unagi.newChan pure DataRecycler { drDump = Unagi.writeChan recycleWrite , drWait = do (tryOp, blockOp) <- Unagi.tryReadChan recycleRead res <- Unagi.tryRead tryOp pure $ maybe (Left blockOp) Right res }