module Data.Attoparsec.Time.Internal
(
TimeOfDay64(..)
, fromPico
, toPico
, diffTimeOfDay64
, toTimeOfDay64
) where
import Prelude ()
import Prelude.Compat
import Data.Int (Int64)
import Data.Time
import Unsafe.Coerce (unsafeCoerce)
#if MIN_VERSION_base(4,7,0)
import Data.Fixed (Pico, Fixed(MkFixed))
toPico :: Integer -> Pico
toPico = MkFixed
fromPico :: Pico -> Integer
fromPico (MkFixed i) = i
#else
import Data.Fixed (Pico)
toPico :: Integer -> Pico
toPico = unsafeCoerce
fromPico :: Pico -> Integer
fromPico = unsafeCoerce
#endif
data TimeOfDay64 = TOD !Int
!Int
!Int64
diffTimeOfDay64 :: DiffTime -> TimeOfDay64
diffTimeOfDay64 t = TOD (fromIntegral h) (fromIntegral m) s
where (h,mp) = fromIntegral pico `quotRem` 3600000000000000
(m,s) = mp `quotRem` 60000000000000
pico = unsafeCoerce t :: Integer
toTimeOfDay64 :: TimeOfDay -> TimeOfDay64
toTimeOfDay64 (TimeOfDay h m s) = TOD h m (fromIntegral (fromPico s))