{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module      :  Mcmc.Monitor.Time
-- Description :  Print time related values
-- Copyright   :  (c) Dominik Schrempf, 2020
-- License     :  GPL-3.0-or-later
--
-- Maintainer  :  dominik.schrempf@gmail.com
-- Stability   :  unstable
-- Portability :  portable
--
-- Creation date: Fri May 29 12:36:43 2020.
module Mcmc.Monitor.Time
  ( renderDuration,
    renderDurationS,
  )
where

import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Time.Clock
import Mcmc.Internal.ByteString

-- | Adapted from System.ProgressBar.renderDuration of package
-- [terminal-progressbar-0.4.1](https://hackage.haskell.org/package/terminal-progress-bar-0.4.1).
renderDuration :: NominalDiffTime -> BL.ByteString
renderDuration :: NominalDiffTime -> ByteString
renderDuration NominalDiffTime
dt = ByteString
hTxt ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
mTxt ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
sTxt
  where
    hTxt :: ByteString
hTxt = Int -> ByteString
renderDecimal Int
h ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
":"
    mTxt :: ByteString
mTxt = Int -> ByteString
renderDecimal Int
m ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
":"
    sTxt :: ByteString
sTxt = Int -> ByteString
renderDecimal Int
s
    (Int
h, Int
hRem) = Int
ts Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
3600
    (Int
m, Int
s) = Int
hRem Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
60
    -- Total amount of seconds
    ts :: Int
    ts :: Int
ts = NominalDiffTime -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round NominalDiffTime
dt
    renderDecimal :: Int -> ByteString
renderDecimal Int
n = Char -> Int -> ByteString -> ByteString
alignRightWith Char
'0' Int
2 (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
BB.toLazyByteString (Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Builder
BB.intDec Int
n

-- | Render duration in seconds.
renderDurationS :: NominalDiffTime -> BL.ByteString
renderDurationS :: NominalDiffTime -> ByteString
renderDurationS NominalDiffTime
dt = Builder -> ByteString
BB.toLazyByteString (Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Builder
BB.intDec Int
ts
  where
    ts :: Int
    ts :: Int
ts = NominalDiffTime -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round NominalDiffTime
dt