{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DerivingVia                #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Ouroboros.Consensus.BlockchainTime.WallClock.Types (
    -- * System time
    SystemStart (..)
    -- * Relative time
  , RelativeTime (..)
  , addRelTime
  , diffRelTime
  , fromRelativeTime
  , toRelativeTime
    -- * Get current time (as 'RelativeTime')
  , SystemTime (..)
    -- * Slot length
  , getSlotLength
  , mkSlotLength
    -- ** Conversions
  , slotLengthFromMillisec
  , slotLengthFromSec
  , slotLengthToMillisec
  , slotLengthToSec
    -- ** opaque
  , SlotLength
  ) where

import           Data.Time.Clock (NominalDiffTime)
import           NoThunks.Class (NoThunks, OnlyCheckWhnfNamed (..))

import           Cardano.Slotting.Time

addRelTime :: NominalDiffTime -> RelativeTime -> RelativeTime
addRelTime :: NominalDiffTime -> RelativeTime -> RelativeTime
addRelTime = NominalDiffTime -> RelativeTime -> RelativeTime
addRelativeTime

diffRelTime :: RelativeTime -> RelativeTime -> NominalDiffTime
diffRelTime :: RelativeTime -> RelativeTime -> NominalDiffTime
diffRelTime = RelativeTime -> RelativeTime -> NominalDiffTime
diffRelativeTime

{-------------------------------------------------------------------------------
  Get current time (as RelativeTime)
-------------------------------------------------------------------------------}

-- | System time
--
-- Slots are counted from the system start.
data SystemTime m = SystemTime {
      -- | Get current time (as a 'RelativeTime')
      --
      -- For real deployment, this will take the current 'UTCTime' and then
      -- subtract the 'SystemStart' (see 'defaultSystemTime'). Tests don't
      -- bother with a 'UTCTime' and just work entirely in 'RelativeTime'.
      SystemTime m -> m RelativeTime
systemTimeCurrent :: m RelativeTime

      -- | Wait for 'SystemStart'
      --
      -- For the real deployment, this waits for the current 'UTCTime'
      -- to reach 'SystemStart'. In tests this does nothing.
    , SystemTime m -> m ()
systemTimeWait    :: m ()
    }
  deriving Context -> SystemTime m -> IO (Maybe ThunkInfo)
Proxy (SystemTime m) -> String
(Context -> SystemTime m -> IO (Maybe ThunkInfo))
-> (Context -> SystemTime m -> IO (Maybe ThunkInfo))
-> (Proxy (SystemTime m) -> String)
-> NoThunks (SystemTime m)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *).
Context -> SystemTime m -> IO (Maybe ThunkInfo)
forall (m :: * -> *). Proxy (SystemTime m) -> String
showTypeOf :: Proxy (SystemTime m) -> String
$cshowTypeOf :: forall (m :: * -> *). Proxy (SystemTime m) -> String
wNoThunks :: Context -> SystemTime m -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *).
Context -> SystemTime m -> IO (Maybe ThunkInfo)
noThunks :: Context -> SystemTime m -> IO (Maybe ThunkInfo)
$cnoThunks :: forall (m :: * -> *).
Context -> SystemTime m -> IO (Maybe ThunkInfo)
NoThunks via OnlyCheckWhnfNamed "SystemTime" (SystemTime m)