File: System.hs

package info (click to toggle)
ghc 9.10.3-1
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 168,924 kB
  • sloc: haskell: 713,548; ansic: 84,223; cpp: 30,255; javascript: 9,003; sh: 7,870; fortran: 3,527; python: 3,228; asm: 2,523; makefile: 2,326; yacc: 1,570; lisp: 532; xml: 196; perl: 111; csh: 2
file content (75 lines) | stat: -rw-r--r-- 2,818 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
{-# LANGUAGE Safe #-}

-- | Fast access to the system clock.
module Data.Time.Clock.System (
    systemEpochDay,
    SystemTime (..),
    truncateSystemTimeLeapSecond,
    getSystemTime,
    systemToUTCTime,
    utcToSystemTime,
    systemToTAITime,
) where

import Data.Int (Int64)
import Data.Time.Calendar.Days
import Data.Time.Clock.Internal.AbsoluteTime
import Data.Time.Clock.Internal.DiffTime
import Data.Time.Clock.Internal.SystemTime
import Data.Time.Clock.Internal.UTCTime

-- | Map leap-second values to the start of the following second.
-- The resulting 'systemNanoseconds' will always be in the range 0 to 1E9-1.
truncateSystemTimeLeapSecond :: SystemTime -> SystemTime
truncateSystemTimeLeapSecond (MkSystemTime seconds nanoseconds)
    | nanoseconds >= 1000000000 = MkSystemTime (succ seconds) 0
truncateSystemTimeLeapSecond t = t

-- | Convert 'SystemTime' to 'UTCTime', matching zero 'SystemTime' to midnight of 'systemEpochDay' UTC.
systemToUTCTime :: SystemTime -> UTCTime
systemToUTCTime (MkSystemTime seconds nanoseconds) = let
    days :: Int64
    timeSeconds :: Int64
    (days, timeSeconds) = seconds `divMod` 86400
    day :: Day
    day = addDays (fromIntegral days) systemEpochDay
    timeNanoseconds :: Int64
    timeNanoseconds = timeSeconds * 1000000000 + (fromIntegral nanoseconds)
    timePicoseconds :: Int64
    timePicoseconds = timeNanoseconds * 1000
    time :: DiffTime
    time = picosecondsToDiffTime $ fromIntegral timePicoseconds
    in UTCTime day time

-- | Convert 'UTCTime' to 'SystemTime', matching zero 'SystemTime' to midnight of 'systemEpochDay' UTC.
utcToSystemTime :: UTCTime -> SystemTime
utcToSystemTime (UTCTime day time) = let
    days :: Int64
    days = fromIntegral $ diffDays day systemEpochDay
    timePicoseconds :: Int64
    timePicoseconds = fromIntegral $ diffTimeToPicoseconds time
    timeNanoseconds :: Int64
    timeNanoseconds = timePicoseconds `div` 1000
    timeSeconds :: Int64
    nanoseconds :: Int64
    (timeSeconds, nanoseconds) =
        if timeNanoseconds >= 86400000000000
            then (86399, timeNanoseconds - 86399000000000)
            else timeNanoseconds `divMod` 1000000000
    seconds :: Int64
    seconds = days * 86400 + timeSeconds
    in MkSystemTime seconds $ fromIntegral nanoseconds

systemEpochAbsolute :: AbsoluteTime
systemEpochAbsolute = taiNominalDayStart systemEpochDay

-- | Convert 'SystemTime' to 'AbsoluteTime', matching zero 'SystemTime' to midnight of 'systemEpochDay' TAI.
systemToTAITime :: SystemTime -> AbsoluteTime
systemToTAITime (MkSystemTime s ns) = let
    diff :: DiffTime
    diff = (fromIntegral s) + (fromIntegral ns) * 1E-9
    in addAbsoluteTime diff systemEpochAbsolute

-- | The day of the epoch of 'SystemTime', 1970-01-01
systemEpochDay :: Day
systemEpochDay = ModifiedJulianDay 40587