{-# LANGUAGE UndecidableInstances #-} module Blucontrol.Control.Wait ( ControlWaitT , runControlWaitT , ConfigWait (..) , Microseconds ) where import Control.Concurrent (threadDelay) import Control.DeepSeq import Control.Monad.Base import Control.Monad.Trans.Control import Control.Monad.Reader import Data.Default import GHC.Generics import Blucontrol.Control newtype ControlWaitT m a = ControlWaitT { ControlWaitT m a -> ReaderT ConfigWait m a unControlWaitT :: ReaderT ConfigWait m a } deriving (Functor (ControlWaitT m) a -> ControlWaitT m a Functor (ControlWaitT m) -> (forall a. a -> ControlWaitT m a) -> (forall a b. ControlWaitT m (a -> b) -> ControlWaitT m a -> ControlWaitT m b) -> (forall a b c. (a -> b -> c) -> ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m c) -> (forall a b. ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b) -> (forall a b. ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m a) -> Applicative (ControlWaitT m) ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m a ControlWaitT m (a -> b) -> ControlWaitT m a -> ControlWaitT m b (a -> b -> c) -> ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m c forall a. a -> ControlWaitT m a forall a b. ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m a forall a b. ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b forall a b. ControlWaitT m (a -> b) -> ControlWaitT m a -> ControlWaitT m b forall a b c. (a -> b -> c) -> ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m c forall (f :: * -> *). Functor f -> (forall a. a -> f a) -> (forall a b. f (a -> b) -> f a -> f b) -> (forall a b c. (a -> b -> c) -> f a -> f b -> f c) -> (forall a b. f a -> f b -> f b) -> (forall a b. f a -> f b -> f a) -> Applicative f forall (m :: * -> *). Applicative m => Functor (ControlWaitT m) forall (m :: * -> *) a. Applicative m => a -> ControlWaitT m a forall (m :: * -> *) a b. Applicative m => ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m a forall (m :: * -> *) a b. Applicative m => ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b forall (m :: * -> *) a b. Applicative m => ControlWaitT m (a -> b) -> ControlWaitT m a -> ControlWaitT m b forall (m :: * -> *) a b c. Applicative m => (a -> b -> c) -> ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m c <* :: ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m a $c<* :: forall (m :: * -> *) a b. Applicative m => ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m a *> :: ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b $c*> :: forall (m :: * -> *) a b. Applicative m => ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b liftA2 :: (a -> b -> c) -> ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m c $cliftA2 :: forall (m :: * -> *) a b c. Applicative m => (a -> b -> c) -> ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m c <*> :: ControlWaitT m (a -> b) -> ControlWaitT m a -> ControlWaitT m b $c<*> :: forall (m :: * -> *) a b. Applicative m => ControlWaitT m (a -> b) -> ControlWaitT m a -> ControlWaitT m b pure :: a -> ControlWaitT m a $cpure :: forall (m :: * -> *) a. Applicative m => a -> ControlWaitT m a $cp1Applicative :: forall (m :: * -> *). Applicative m => Functor (ControlWaitT m) Applicative, a -> ControlWaitT m b -> ControlWaitT m a (a -> b) -> ControlWaitT m a -> ControlWaitT m b (forall a b. (a -> b) -> ControlWaitT m a -> ControlWaitT m b) -> (forall a b. a -> ControlWaitT m b -> ControlWaitT m a) -> Functor (ControlWaitT m) forall a b. a -> ControlWaitT m b -> ControlWaitT m a forall a b. (a -> b) -> ControlWaitT m a -> ControlWaitT m b forall (m :: * -> *) a b. Functor m => a -> ControlWaitT m b -> ControlWaitT m a forall (m :: * -> *) a b. Functor m => (a -> b) -> ControlWaitT m a -> ControlWaitT m b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: a -> ControlWaitT m b -> ControlWaitT m a $c<$ :: forall (m :: * -> *) a b. Functor m => a -> ControlWaitT m b -> ControlWaitT m a fmap :: (a -> b) -> ControlWaitT m a -> ControlWaitT m b $cfmap :: forall (m :: * -> *) a b. Functor m => (a -> b) -> ControlWaitT m a -> ControlWaitT m b Functor, Applicative (ControlWaitT m) a -> ControlWaitT m a Applicative (ControlWaitT m) -> (forall a b. ControlWaitT m a -> (a -> ControlWaitT m b) -> ControlWaitT m b) -> (forall a b. ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b) -> (forall a. a -> ControlWaitT m a) -> Monad (ControlWaitT m) ControlWaitT m a -> (a -> ControlWaitT m b) -> ControlWaitT m b ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b forall a. a -> ControlWaitT m a forall a b. ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b forall a b. ControlWaitT m a -> (a -> ControlWaitT m b) -> ControlWaitT m b forall (m :: * -> *). Monad m => Applicative (ControlWaitT m) forall (m :: * -> *) a. Monad m => a -> ControlWaitT m a forall (m :: * -> *) a b. Monad m => ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b forall (m :: * -> *) a b. Monad m => ControlWaitT m a -> (a -> ControlWaitT m b) -> ControlWaitT m b forall (m :: * -> *). Applicative m -> (forall a b. m a -> (a -> m b) -> m b) -> (forall a b. m a -> m b -> m b) -> (forall a. a -> m a) -> Monad m return :: a -> ControlWaitT m a $creturn :: forall (m :: * -> *) a. Monad m => a -> ControlWaitT m a >> :: ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b $c>> :: forall (m :: * -> *) a b. Monad m => ControlWaitT m a -> ControlWaitT m b -> ControlWaitT m b >>= :: ControlWaitT m a -> (a -> ControlWaitT m b) -> ControlWaitT m b $c>>= :: forall (m :: * -> *) a b. Monad m => ControlWaitT m a -> (a -> ControlWaitT m b) -> ControlWaitT m b $cp1Monad :: forall (m :: * -> *). Monad m => Applicative (ControlWaitT m) Monad, MonadBase b, MonadBaseControl b, m a -> ControlWaitT m a (forall (m :: * -> *) a. Monad m => m a -> ControlWaitT m a) -> MonadTrans ControlWaitT forall (m :: * -> *) a. Monad m => m a -> ControlWaitT m a forall (t :: (* -> *) -> * -> *). (forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t lift :: m a -> ControlWaitT m a $clift :: forall (m :: * -> *) a. Monad m => m a -> ControlWaitT m a MonadTrans, MonadTrans ControlWaitT m (StT ControlWaitT a) -> ControlWaitT m a MonadTrans ControlWaitT -> (forall (m :: * -> *) a. Monad m => (Run ControlWaitT -> m a) -> ControlWaitT m a) -> (forall (m :: * -> *) a. Monad m => m (StT ControlWaitT a) -> ControlWaitT m a) -> MonadTransControl ControlWaitT (Run ControlWaitT -> m a) -> ControlWaitT m a forall (m :: * -> *) a. Monad m => m (StT ControlWaitT a) -> ControlWaitT m a forall (m :: * -> *) a. Monad m => (Run ControlWaitT -> m a) -> ControlWaitT m a forall (t :: (* -> *) -> * -> *). MonadTrans t -> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a) -> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a) -> MonadTransControl t restoreT :: m (StT ControlWaitT a) -> ControlWaitT m a $crestoreT :: forall (m :: * -> *) a. Monad m => m (StT ControlWaitT a) -> ControlWaitT m a liftWith :: (Run ControlWaitT -> m a) -> ControlWaitT m a $cliftWith :: forall (m :: * -> *) a. Monad m => (Run ControlWaitT -> m a) -> ControlWaitT m a $cp1MonadTransControl :: MonadTrans ControlWaitT MonadTransControl) instance MonadBaseControl IO m => MonadControl (ControlWaitT m) where type ControlConstraint (ControlWaitT m) _ = () doInbetween :: a -> ControlWaitT m () doInbetween a _ = IO () -> ControlWaitT m () forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α liftBase (IO () -> ControlWaitT m ()) -> (ConfigWait -> IO ()) -> ConfigWait -> ControlWaitT m () forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> IO () threadDelay (Int -> IO ()) -> (ConfigWait -> Int) -> ConfigWait -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c . ConfigWait -> Int interval (ConfigWait -> ControlWaitT m ()) -> ControlWaitT m ConfigWait -> ControlWaitT m () forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<< ReaderT ConfigWait m ConfigWait -> ControlWaitT m ConfigWait forall (m :: * -> *) a. ReaderT ConfigWait m a -> ControlWaitT m a ControlWaitT ReaderT ConfigWait m ConfigWait forall r (m :: * -> *). MonadReader r m => m r ask runControlWaitT :: ConfigWait -> ControlWaitT m a -> m a runControlWaitT :: ConfigWait -> ControlWaitT m a -> m a runControlWaitT ConfigWait conf ControlWaitT m a tma = ReaderT ConfigWait m a -> ConfigWait -> m a forall r (m :: * -> *) a. ReaderT r m a -> r -> m a runReaderT (ControlWaitT m a -> ReaderT ConfigWait m a forall (m :: * -> *) a. ControlWaitT m a -> ReaderT ConfigWait m a unControlWaitT ControlWaitT m a tma) ConfigWait conf newtype ConfigWait = ConfigWait { ConfigWait -> Int interval :: Microseconds } deriving (ConfigWait -> ConfigWait -> Bool (ConfigWait -> ConfigWait -> Bool) -> (ConfigWait -> ConfigWait -> Bool) -> Eq ConfigWait forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ConfigWait -> ConfigWait -> Bool $c/= :: ConfigWait -> ConfigWait -> Bool == :: ConfigWait -> ConfigWait -> Bool $c== :: ConfigWait -> ConfigWait -> Bool Eq, (forall x. ConfigWait -> Rep ConfigWait x) -> (forall x. Rep ConfigWait x -> ConfigWait) -> Generic ConfigWait forall x. Rep ConfigWait x -> ConfigWait forall x. ConfigWait -> Rep ConfigWait x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ConfigWait x -> ConfigWait $cfrom :: forall x. ConfigWait -> Rep ConfigWait x Generic, Eq ConfigWait Eq ConfigWait -> (ConfigWait -> ConfigWait -> Ordering) -> (ConfigWait -> ConfigWait -> Bool) -> (ConfigWait -> ConfigWait -> Bool) -> (ConfigWait -> ConfigWait -> Bool) -> (ConfigWait -> ConfigWait -> Bool) -> (ConfigWait -> ConfigWait -> ConfigWait) -> (ConfigWait -> ConfigWait -> ConfigWait) -> Ord ConfigWait ConfigWait -> ConfigWait -> Bool ConfigWait -> ConfigWait -> Ordering ConfigWait -> ConfigWait -> ConfigWait forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ConfigWait -> ConfigWait -> ConfigWait $cmin :: ConfigWait -> ConfigWait -> ConfigWait max :: ConfigWait -> ConfigWait -> ConfigWait $cmax :: ConfigWait -> ConfigWait -> ConfigWait >= :: ConfigWait -> ConfigWait -> Bool $c>= :: ConfigWait -> ConfigWait -> Bool > :: ConfigWait -> ConfigWait -> Bool $c> :: ConfigWait -> ConfigWait -> Bool <= :: ConfigWait -> ConfigWait -> Bool $c<= :: ConfigWait -> ConfigWait -> Bool < :: ConfigWait -> ConfigWait -> Bool $c< :: ConfigWait -> ConfigWait -> Bool compare :: ConfigWait -> ConfigWait -> Ordering $ccompare :: ConfigWait -> ConfigWait -> Ordering $cp1Ord :: Eq ConfigWait Ord, ReadPrec [ConfigWait] ReadPrec ConfigWait Int -> ReadS ConfigWait ReadS [ConfigWait] (Int -> ReadS ConfigWait) -> ReadS [ConfigWait] -> ReadPrec ConfigWait -> ReadPrec [ConfigWait] -> Read ConfigWait forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [ConfigWait] $creadListPrec :: ReadPrec [ConfigWait] readPrec :: ReadPrec ConfigWait $creadPrec :: ReadPrec ConfigWait readList :: ReadS [ConfigWait] $creadList :: ReadS [ConfigWait] readsPrec :: Int -> ReadS ConfigWait $creadsPrec :: Int -> ReadS ConfigWait Read, Int -> ConfigWait -> ShowS [ConfigWait] -> ShowS ConfigWait -> String (Int -> ConfigWait -> ShowS) -> (ConfigWait -> String) -> ([ConfigWait] -> ShowS) -> Show ConfigWait forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ConfigWait] -> ShowS $cshowList :: [ConfigWait] -> ShowS show :: ConfigWait -> String $cshow :: ConfigWait -> String showsPrec :: Int -> ConfigWait -> ShowS $cshowsPrec :: Int -> ConfigWait -> ShowS Show) instance NFData ConfigWait instance Default ConfigWait where def :: ConfigWait def = ConfigWait :: Int -> ConfigWait ConfigWait { interval :: Int interval = Int 1000000 } type Microseconds = Int