-----------------------------------------------------------------------------
--
-- Module      :  Data.Time.Util
-- Copyright   :  (c) 2012-16 Brian W Bush
-- License     :  MIT
--
-- Maintainer  :  Brian W Bush <consult@brianwbush.info>
-- Stability   :  Stable
-- Portability :  Portable
--
-- | Some POSIX time functions.
--
-----------------------------------------------------------------------------


{-# LANGUAGE Safe #-}


module Data.Time.Util (
-- Types
  SecondsPOSIX
-- Conversions
, toSecondsPOSIX
, fromSecondsPOSIX
, getSecondsPOSIX
) where


import Control.Arrow (second)
import Data.Time.Clock (getCurrentTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime, utcTimeToPOSIXSeconds)
import Data.Time.Format (defaultTimeLocale, formatTime, parseTimeOrError)
import Data.Time.LocalTime (TimeZone, utcToZonedTime, zonedTimeToUTC)


-- | POSIX seconds.
type SecondsPOSIX = Int


theFormat :: String
theFormat = "%FT%X%z %Z"


-- | Convert an ISO 8601 string to POSIX seconds.
toSecondsPOSIX :: String -> SecondsPOSIX
toSecondsPOSIX =
  truncate
    . utcTimeToPOSIXSeconds
    . zonedTimeToUTC
    . parseTimeOrError False defaultTimeLocale theFormat


-- | Convert POSIX seconds to an ISO 8601 string.
fromSecondsPOSIX :: TimeZone -> SecondsPOSIX -> String
fromSecondsPOSIX zone =
  uncurry (++)
    . second (':' :)
    . splitAt 22
    . formatTime defaultTimeLocale theFormat
    . utcToZonedTime zone
    . posixSecondsToUTCTime
    . fromIntegral


-- | Get the current time. 
getSecondsPOSIX :: IO SecondsPOSIX
getSecondsPOSIX =
  truncate
    . utcTimeToPOSIXSeconds
    <$> getCurrentTime