{-# LANGUAGE NoImplicitPrelude #-}
module Data.Attoparsec.Time.Internal
    (
      TimeOfDay64(..)
    , fromPico
    , toPico
    , diffTimeOfDay64
    , toTimeOfDay64
    ) where
import Prelude.Compat
import Data.Fixed (Fixed(MkFixed), Pico)
import Data.Int (Int64)
import Data.Time (TimeOfDay(..))
import Data.Time.Clock.Compat
toPico :: Integer -> Pico
toPico = MkFixed
fromPico :: Pico -> Integer
fromPico (MkFixed i) = i
data TimeOfDay64 = TOD {-# UNPACK #-} !Int
                       {-# UNPACK #-} !Int
                       {-# UNPACK #-} !Int64
posixDayLength :: DiffTime
posixDayLength = 86400
diffTimeOfDay64 :: DiffTime -> TimeOfDay64
diffTimeOfDay64 t
  | t >= posixDayLength = TOD 23 59 (60000000000000 + pico (t - posixDayLength))
  | otherwise = TOD (fromIntegral h) (fromIntegral m) s
    where (h,mp) = pico t `quotRem` 3600000000000000
          (m,s)  = mp `quotRem` 60000000000000
          pico   = fromIntegral . diffTimeToPicoseconds
toTimeOfDay64 :: TimeOfDay -> TimeOfDay64
toTimeOfDay64 (TimeOfDay h m s) = TOD h m (fromIntegral (fromPico s))