{-# LANGUAGE Safe #-}
module System.Time.Utils(
timelocal,
timegm,
timeDiffToSecs,
epoch,
epochToClockTime,
clockTimeToEpoch,
renderSecs, renderTD
)
where
import safe Data.Ratio ( (%) )
import safe System.Time
( diffClockTimes,
normalizeTimeDiff,
toCalendarTime,
toClockTime,
CalendarTime(..),
ClockTime(..),
Day(Thursday),
Month(January),
TimeDiff(TimeDiff, tdSec, tdMin, tdHour, tdDay, tdMonth, tdYear) )
epoch :: CalendarTime
epoch :: CalendarTime
epoch = CalendarTime { ctYear :: Int
ctYear = Int
1970, ctMonth :: Month
ctMonth = Month
January,
ctDay :: Int
ctDay = Int
1, ctHour :: Int
ctHour = Int
0, ctMin :: Int
ctMin = Int
0, ctSec :: Int
ctSec = Int
0,
ctPicosec :: Integer
ctPicosec = Integer
0, ctWDay :: Day
ctWDay = Day
Thursday, ctYDay :: Int
ctYDay = Int
0,
ctTZName :: String
ctTZName = String
"UTC", ctTZ :: Int
ctTZ = Int
0, ctIsDST :: Bool
ctIsDST = Bool
False}
timegm :: CalendarTime -> Integer
timegm :: CalendarTime -> Integer
timegm CalendarTime
ct =
TimeDiff -> Integer
timeDiffToSecs (ClockTime -> ClockTime -> TimeDiff
diffClockTimes (CalendarTime -> ClockTime
toClockTime CalendarTime
ct) (CalendarTime -> ClockTime
toClockTime CalendarTime
epoch))
timelocal :: CalendarTime -> IO Integer
timelocal :: CalendarTime -> IO Integer
timelocal CalendarTime
ct =
do CalendarTime
guessct <- ClockTime -> IO CalendarTime
toCalendarTime ClockTime
guesscl
let newct :: CalendarTime
newct = CalendarTime
ct {ctTZ :: Int
ctTZ = CalendarTime -> Int
ctTZ CalendarTime
guessct}
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ CalendarTime -> Integer
timegm CalendarTime
newct
where guesscl :: ClockTime
guesscl = CalendarTime -> ClockTime
toClockTime CalendarTime
ct
timeDiffToSecs :: TimeDiff -> Integer
timeDiffToSecs :: TimeDiff -> Integer
timeDiffToSecs TimeDiff
td =
(forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeDiff -> Int
tdSec TimeDiff
td) forall a. Num a => a -> a -> a
+
Integer
60 forall a. Num a => a -> a -> a
* ((forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeDiff -> Int
tdMin TimeDiff
td) forall a. Num a => a -> a -> a
+
Integer
60 forall a. Num a => a -> a -> a
* ((forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeDiff -> Int
tdHour TimeDiff
td) forall a. Num a => a -> a -> a
+
Integer
24 forall a. Num a => a -> a -> a
* ((forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeDiff -> Int
tdDay TimeDiff
td) forall a. Num a => a -> a -> a
+
Integer
30 forall a. Num a => a -> a -> a
* ((forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeDiff -> Int
tdMonth TimeDiff
td) forall a. Num a => a -> a -> a
+
Integer
365 forall a. Num a => a -> a -> a
* (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeDiff -> Int
tdYear TimeDiff
td)))))
epochToClockTime :: Real a => a -> ClockTime
epochToClockTime :: forall a. Real a => a -> ClockTime
epochToClockTime a
x =
Integer -> Integer -> ClockTime
TOD Integer
seconds Integer
secfrac
where ratval :: Rational
ratval = forall a. Real a => a -> Rational
toRational a
x
seconds :: Integer
seconds = forall a b. (RealFrac a, Integral b) => a -> b
floor Rational
ratval
secfrac :: Integer
secfrac = forall a b. (RealFrac a, Integral b) => a -> b
floor forall a b. (a -> b) -> a -> b
$ (Rational
ratval forall a. Num a => a -> a -> a
- (Integer
seconds forall a. Integral a => a -> a -> Ratio a
% Integer
1) ) forall a. Num a => a -> a -> a
* Rational
picosecondfactor
picosecondfactor :: Rational
picosecondfactor = Rational
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
12 :: Integer)
clockTimeToEpoch :: Num a => ClockTime -> a
clockTimeToEpoch :: forall a. Num a => ClockTime -> a
clockTimeToEpoch (TOD Integer
sec Integer
_) = forall a. Num a => Integer -> a
fromInteger Integer
sec
renderSecs :: Integer -> String
renderSecs :: Integer -> String
renderSecs Integer
i = TimeDiff -> String
renderTD forall a b. (a -> b) -> a -> b
$ ClockTime -> ClockTime -> TimeDiff
diffClockTimes (Integer -> Integer -> ClockTime
TOD Integer
i Integer
0) (Integer -> Integer -> ClockTime
TOD Integer
0 Integer
0)
renderTD :: TimeDiff -> String
renderTD :: TimeDiff -> String
renderTD TimeDiff
itd =
case [(Int, Char)]
workinglist of
[] -> String
"0s"
[(Int, Char)]
_ -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\(Int
q, Char
s) -> forall a. Show a => a -> String
show Int
q forall a. [a] -> [a] -> [a]
++ [Char
s]) forall a b. (a -> b) -> a -> b
$ [(Int, Char)]
workinglist
where td :: TimeDiff
td = TimeDiff -> TimeDiff
normalizeTimeDiff TimeDiff
itd
suffixlist :: String
suffixlist = String
"yMdhms"
quantlist :: [Int]
quantlist = (\(TimeDiff Int
y Int
mo Int
d Int
h Int
m Int
s Integer
_) -> [Int
y, Int
mo, Int
d, Int
h, Int
m, Int
s]) TimeDiff
td
zippedlist :: [(Int, Char)]
zippedlist = forall a b. [a] -> [b] -> [(a, b)]
zip [Int]
quantlist String
suffixlist
workinglist :: [(Int, Char)]
workinglist = forall a. Int -> [a] -> [a]
take Int
2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile (\(Int
q, Char
_) -> Int
q forall a. Eq a => a -> a -> Bool
== Int
0) forall a b. (a -> b) -> a -> b
$ [(Int, Char)]
zippedlist