{-# LANGUAGE ScopedTypeVariables #-}
module Control.Debounce.Internal (
DebounceSettings(..)
, DebounceEdge(..)
, leadingEdge
, trailingEdge
, mkDebounceInternal
) where
import Control.Concurrent (forkIO)
import Control.Concurrent.MVar (takeMVar, tryPutMVar, tryTakeMVar, MVar)
import Control.Exception (SomeException, handle, mask_)
import Control.Monad (forever, void)
data DebounceSettings = DebounceSettings
{ DebounceSettings -> Int
debounceFreq :: Int
, DebounceSettings -> IO ()
debounceAction :: IO ()
, DebounceSettings -> DebounceEdge
debounceEdge :: DebounceEdge
}
data DebounceEdge =
Leading
| Trailing
deriving (Int -> DebounceEdge -> ShowS
[DebounceEdge] -> ShowS
DebounceEdge -> String
(Int -> DebounceEdge -> ShowS)
-> (DebounceEdge -> String)
-> ([DebounceEdge] -> ShowS)
-> Show DebounceEdge
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DebounceEdge -> ShowS
showsPrec :: Int -> DebounceEdge -> ShowS
$cshow :: DebounceEdge -> String
show :: DebounceEdge -> String
$cshowList :: [DebounceEdge] -> ShowS
showList :: [DebounceEdge] -> ShowS
Show, DebounceEdge -> DebounceEdge -> Bool
(DebounceEdge -> DebounceEdge -> Bool)
-> (DebounceEdge -> DebounceEdge -> Bool) -> Eq DebounceEdge
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DebounceEdge -> DebounceEdge -> Bool
== :: DebounceEdge -> DebounceEdge -> Bool
$c/= :: DebounceEdge -> DebounceEdge -> Bool
/= :: DebounceEdge -> DebounceEdge -> Bool
Eq)
leadingEdge :: DebounceEdge
leadingEdge :: DebounceEdge
leadingEdge = DebounceEdge
Leading
trailingEdge :: DebounceEdge
trailingEdge :: DebounceEdge
trailingEdge = DebounceEdge
Trailing
mkDebounceInternal :: MVar () -> (Int -> IO ()) -> DebounceSettings -> IO (IO ())
mkDebounceInternal :: MVar () -> (Int -> IO ()) -> DebounceSettings -> IO (IO ())
mkDebounceInternal MVar ()
baton Int -> IO ()
delayFn (DebounceSettings Int
freq IO ()
action DebounceEdge
edge) = do
IO () -> IO ()
forall a. IO a -> IO a
mask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO ThreadId -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ThreadId -> IO ()) -> IO ThreadId -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
MVar () -> IO ()
forall a. MVar a -> IO a
takeMVar MVar ()
baton
case DebounceEdge
edge of
DebounceEdge
Leading -> do
IO () -> IO ()
ignoreExc IO ()
action
Int -> IO ()
delayFn Int
freq
DebounceEdge
Trailing -> do
Int -> IO ()
delayFn Int
freq
IO (Maybe ()) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (Maybe ()) -> IO ()) -> IO (Maybe ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ MVar () -> IO (Maybe ())
forall a. MVar a -> IO (Maybe a)
tryTakeMVar MVar ()
baton
IO () -> IO ()
ignoreExc IO ()
action
IO () -> IO (IO ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IO () -> IO (IO ())) -> IO () -> IO (IO ())
forall a b. (a -> b) -> a -> b
$ IO Bool -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ MVar () -> () -> IO Bool
forall a. MVar a -> a -> IO Bool
tryPutMVar MVar ()
baton ()
ignoreExc :: IO () -> IO ()
ignoreExc :: IO () -> IO ()
ignoreExc = (SomeException -> IO ()) -> IO () -> IO ()
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle ((SomeException -> IO ()) -> IO () -> IO ())
-> (SomeException -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ \(SomeException
_ :: SomeException) -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()