module Ros.Internal.RosTime (ROSTime, ROSDuration, toROSTime, fromROSTime,
diffROSTime, getROSTime, diffSeconds) where
import Data.Time.Clock (UTCTime, NominalDiffTime)
import Data.Time.Clock.POSIX
import Data.Word (Word32)
import Ros.Internal.RosTypes
toROSTime :: UTCTime -> ROSTime
toROSTime = aux . properFraction . utcTimeToPOSIXSeconds
where aux (s,f) = (s, truncate $ f * 1000000)
class FromROSTime a where
fromROSTime :: ROSTime -> a
instance FromROSTime UTCTime where
fromROSTime = posixSecondsToUTCTime . aux . fromROSTime
where aux = realToFrac :: Double -> NominalDiffTime
instance FromROSTime Double where
fromROSTime (s,ns) = s' + ns'
where s' = fromIntegral s :: Double
ns' = fromIntegral ns / 1000000 :: Double
diffROSTime :: ROSTime -> ROSTime -> ROSDuration
diffROSTime (s1,ns1) (s2,ns2)
| dns >= 0 = (fi ds, fi dns)
| otherwise = (fi $ ds 1, fi $ 1000000 + dns)
where dns = fw ns1 fw ns2
ds = fw s1 fw s2
fw :: Word32 -> Int
fw = fromIntegral
fi :: Int -> Word32
fi = fromIntegral
getROSTime :: IO ROSTime
getROSTime = fmap (aux . properFraction) getPOSIXTime
where aux (s,f) = (s, truncate $ f * 1000000)
diffSeconds :: ROSTime -> ROSTime -> Double
diffSeconds t1 t2 = fromROSTime $ diffROSTime t1 t2