Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
OSC related timing functions. OSC timestamps are NTP
values,
http://ntp.org/.
- type NTPi = Word64
- type UT = Double
- ntpr_to_ntpi :: RealFrac n => n -> NTPi
- ntpi_to_ntpr :: Fractional n => NTPi -> n
- ntp_ut_epoch_diff :: Num n => n
- ut_to_ntpi :: UT -> NTPi
- ut_to_ntpr :: Num n => n -> n
- ntpr_to_ut :: Num n => n -> n
- ntpi_to_ut :: NTPi -> UT
- ut_epoch :: UTCTime
- utc_to_ut :: Fractional n => UTCTime -> n
- time :: MonadIO m => m Time
- pauseThreadLimit :: Fractional n => n
- pauseThread :: (MonadIO m, Ord n, RealFrac n) => n -> m ()
- wait :: MonadIO m => Double -> m ()
- pauseThreadUntil :: MonadIO m => Time -> m ()
- sleepThread :: (RealFrac n, MonadIO m) => n -> m ()
- sleepThreadUntil :: MonadIO m => Time -> m ()
Temporal types
Time conversion
ntpr_to_ntpi :: RealFrac n => n -> NTPi Source
Convert a real-valued NTP timestamp to an NTPi
timestamp.
ntpi_to_ntpr :: Fractional n => NTPi -> n Source
Convert an NTPi
timestamp to a real-valued NTP timestamp.
ntp_ut_epoch_diff :: Num n => n Source
Difference (in seconds) between NTP and UT epochs.
ntp_ut_epoch_diff / (24 * 60 * 60) == 25567
ut_to_ntpr :: Num n => n -> n Source
Convert Unix/Posix
to NTP
.
ntpr_to_ut :: Num n => n -> n Source
Convert NTP
to Unix/Posix
.
ntpi_to_ut :: NTPi -> UT Source
Convert NTPi
to Unix/Posix
.
Time
inter-operation.
utc_to_ut :: Fractional n => UTCTime -> n Source
Convert UTCTime
to Unix/Posix
.
Clock operations
time :: MonadIO m => m Time Source
Read current real-valued NTP
timestamp.
do {ct <- fmap utc_to_ut T.getCurrentTime ;pt <- fmap realToFrac T.getPOSIXTime ;print (pt - ct,pt - ct < 1e-5)}
Thread operations.
pauseThreadLimit :: Fractional n => n Source
The pauseThread
limit (in seconds). Values larger than this
require a different thread delay mechanism, see sleepThread
. The
value is the number of microseconds in maxBound::Int
.
pauseThread :: (MonadIO m, Ord n, RealFrac n) => n -> m () Source
Pause current thread for the indicated duration (in seconds), see
pauseThreadLimit
.
wait :: MonadIO m => Double -> m () Source
Type restricted pauseThread
.
pauseThreadUntil :: MonadIO m => Time -> m () Source
Pause current thread until the given Time
, see
pauseThreadLimit
.
sleepThread :: (RealFrac n, MonadIO m) => n -> m () Source
Sleep current thread for the indicated duration (in seconds).
Divides long sleeps into parts smaller than pauseThreadLimit
.
sleepThreadUntil :: MonadIO m => Time -> m () Source
Sleep current thread until the given Time
. Divides long sleeps
into parts smaller than pauseThreadLimit
.