module Music.Theory.Concurrent where
import Control.Concurrent
threadDelaySeconds :: RealFrac n => n -> IO ()
threadDelaySeconds :: forall n. RealFrac n => n -> IO ()
threadDelaySeconds = Int -> IO ()
threadDelay forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (RealFrac a, Integral b) => a -> b
floor forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => a -> a -> a
(*) n
1e6
threadDelaySecondsLimit :: Fractional n => n
threadDelaySecondsLimit :: forall n. Fractional n => n
threadDelaySecondsLimit = forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall a. Bounded a => a
maxBound::Int) forall a. Num a => a -> a -> a
- Int
1) forall a. Fractional a => a -> a -> a
/ n
1e6
threadSleepForSeconds :: RealFrac n => n -> IO ()
threadSleepForSeconds :: forall n. RealFrac n => n -> IO ()
threadSleepForSeconds n
n =
if n
n forall a. Ord a => a -> a -> Bool
< forall n. Fractional n => n
threadDelaySecondsLimit
then forall n. RealFrac n => n -> IO ()
threadDelaySeconds n
n
else forall n. RealFrac n => n -> IO ()
threadDelaySeconds (forall n. Fractional n => n
threadDelaySecondsLimit :: Double) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall n. RealFrac n => n -> IO ()
threadSleepForSeconds (n
n forall a. Num a => a -> a -> a
- forall n. Fractional n => n
threadDelaySecondsLimit)