Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
OSC related timing functions.
OSC timestamps are 64-bit NTP
values, http://ntp.org/.
Synopsis
- type NTP64 = Word64
- type Time = Double
- immediately :: Time
- type UT = Double
- ntpr_to_ntpi :: Time -> NTP64
- ntpi_to_ntpr :: NTP64 -> Time
- ntp_ut_epoch_diff :: Num n => n
- ut_to_ntpi :: UT -> NTP64
- ut_to_ntpr :: Num n => n -> n
- ntpr_to_ut :: Num n => n -> n
- ntpi_to_ut :: NTP64 -> UT
- ntpr_to_posixtime :: Time -> POSIXTime
- posixtime_to_ntpr :: POSIXTime -> Time
- ut_epoch :: UTCTime
- utc_to_ut :: Fractional n => UTCTime -> n
- time :: MonadIO m => m Time
- pauseThreadLimit :: Fractional n => n
- pauseThread :: (MonadIO m, 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 ()
- iso_8601_fmt :: String
- iso_8601_to_utctime :: String -> Maybe UTCTime
- utctime_to_iso_8601 :: UTCTime -> String
- ntpr_to_iso_8601 :: Time -> String
- iso_8601_to_ntpr :: String -> Maybe Time
- time_pp :: Time -> String
Temporal types
Type for binary (integeral) representation of a 64-bit NTP
timestamp (ie. ntpi
).
The NTP epoch is January 1, 1900.
NTPv4 also includes a 128-bit format, which is not used by OSC.
NTP
time in real-valued (fractional) form (ie. ntpr
).
This is the primary form of timestamp used by hosc.
immediately :: Time Source #
Constant indicating a bundle to be executed immediately.
It has the NTP64 representation of 1
.
Unix/Posix
time in real-valued (fractional) form.
The Unix/Posix epoch is January 1, 1970.
Time conversion
ntpr_to_ntpi :: Time -> NTP64 Source #
Convert a real-valued NTP timestamp to an NTPi
timestamp.
ntpr_to_ntpi immediately == 1 fmap ntpr_to_ntpi time
ntpi_to_ntpr :: NTP64 -> Time 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 25567 `div` 365 == 70
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 :: NTP64 -> UT Source #
Convert NTPi
to Unix/Posix
.
Time
inter-operation.
Clock operations
time :: MonadIO m => m Time Source #
Read current real-valued NTP
timestamp.
get_ct = fmap utc_to_ut T.getCurrentTime get_pt = fmap realToFrac T.getPOSIXTime (ct,pt) <- get_ct >>= \t0 -> get_pt >>= \t1 -> return (t0,t1) 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, RealFrac n) => n -> m () Source #
Pause current thread for the indicated duration (in seconds), see pauseThreadLimit
.
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
.
Pretty printing
iso_8601_fmt :: String Source #
Detailed 37-character ISO 8601 format, including fractional seconds and '+0000' suffix.
iso_8601_to_utctime :: String -> Maybe UTCTime Source #
Parse time according to iso_8601_fmt
iso_8601_to_utctime "2015-11-26T00:29:37,145875000000+0000"
utctime_to_iso_8601 :: UTCTime -> String Source #
UTC time in iso_8601_fmt
.
tm <- fmap (utctime_to_iso_8601 . T.posixSecondsToUTCTime) T.getPOSIXTime (length tm,sum [4+1+2+1+2,1,2+1+2+1+2,1,12,1,4],sum [10,1,8,1,12,1,4]) == (37,37,37)
ntpr_to_iso_8601 :: Time -> String Source #
ISO 8601 of Time
.
tm <- fmap ntpr_to_iso_8601 time import System.Process {- process -} rawSystem "date" ["-d",tm]
t = 15708783354150518784 s = "2015-11-26T00:22:19,366058349609+0000" ntpr_to_iso_8601 (ntpi_to_ntpr t) == s