module Development.IDE.Core.Debouncer
( Debouncer
, registerEvent
, newAsyncDebouncer
, noopDebouncer
) where
import Control.Concurrent.Extra
import Control.Concurrent.Async
import Control.Exception
import Control.Monad.Extra
import Data.Hashable
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as Map
import System.Time.Extra
newtype Debouncer k = Debouncer { registerEvent :: Seconds -> k -> IO () -> IO () }
newAsyncDebouncer :: (Eq k, Hashable k) => IO (Debouncer k)
newAsyncDebouncer = Debouncer . asyncRegisterEvent <$> newVar Map.empty
asyncRegisterEvent :: (Eq k, Hashable k) => Var (HashMap k (Async ())) -> Seconds -> k -> IO () -> IO ()
asyncRegisterEvent d 0 k fire = do
modifyVar_ d $ \m -> mask_ $ do
whenJust (Map.lookup k m) cancel
pure $ Map.delete k m
fire
asyncRegisterEvent d delay k fire = modifyVar_ d $ \m -> mask_ $ do
whenJust (Map.lookup k m) cancel
a <- asyncWithUnmask $ \unmask -> unmask $ do
sleep delay
fire
modifyVar_ d (pure . Map.delete k)
pure $ Map.insert k a m
noopDebouncer :: Debouncer k
noopDebouncer = Debouncer $ \_ _ a -> a