urbit/pkg/hs/urbit-noun/lib/Urbit/Noun/Time.hs

152 lines
4.4 KiB
Haskell
Raw Normal View History

2020-01-23 07:16:09 +03:00
{-|
TODO This is slow.
-}
2019-05-08 23:00:12 +03:00
module Urbit.Noun.Time where
2019-05-08 21:47:20 +03:00
import Control.Lens
2019-07-12 22:24:44 +03:00
import Prelude
2019-05-08 21:47:20 +03:00
import Data.Bits (shiftL, shiftR, (.&.))
import Data.List (intercalate)
import Data.Time.Calendar (toGregorian)
import Data.Time.Clock (DiffTime, UTCTime(..))
2019-07-12 22:24:44 +03:00
import Data.Time.Clock (diffTimeToPicoseconds, picosecondsToDiffTime)
2019-07-02 05:51:26 +03:00
import Data.Time.Clock.System (SystemTime(..), getSystemTime)
2019-07-12 22:24:44 +03:00
import Data.Time.Clock.System (systemToUTCTime, utcToSystemTime)
import Data.Time.LocalTime (TimeOfDay(..), timeToTimeOfDay)
import Data.Word (Word64)
import Text.Printf (printf)
import Urbit.Noun (FromNoun, ToNoun)
2019-05-08 21:47:20 +03:00
-- Types -----------------------------------------------------------------------
newtype Gap = Gap { _fractoSecs :: Integer }
deriving newtype (Eq, Ord, Show, Num, ToNoun, FromNoun)
2019-05-08 21:47:20 +03:00
newtype Unix = Unix { _sinceUnixEpoch :: Gap }
deriving newtype (Eq, Ord, Show, ToNoun, FromNoun)
2019-05-08 21:47:20 +03:00
newtype Wen = Wen { _sinceUrbitEpoch :: Gap }
2019-08-01 03:27:13 +03:00
deriving newtype (Eq, Ord, Show, Num, ToNoun, FromNoun)
2019-05-08 21:47:20 +03:00
newtype Date = MkDate { _dateWen :: Wen }
deriving newtype (Eq, Ord, Num, ToNoun, FromNoun)
2019-05-08 21:47:20 +03:00
-- Record Lenses ---------------------------------------------------------------
2019-05-08 21:47:20 +03:00
makeLenses ''Gap
makeLenses ''Unix
makeLenses ''Wen
makeLenses ''Date
-- Instances -------------------------------------------------------------------
instance Show Date where
show (MkDate wen) = if fs == 0
then printf "~%i.%u.%u..%02u.%02u.%02u" y m d h min s
else printf "~%i.%u.%u..%02u.%02u.%02u..%s" y m d h min s (showGap fs)
where
utc = wen ^. systemTime . to systemToUTCTime
(y, m, d) = toGregorian (utctDay utc)
TimeOfDay h min (floor -> s::Int) = timeToTimeOfDay (utctDayTime utc)
fs = (wen ^. wenFracto . to (fromIntegral @Integer @Word64))
wenFracto :: Lens' Wen Integer
wenFracto = sinceUrbitEpoch . fractoSecs
showGap :: Word64 -> String
showGap gap = intercalate "." (printf "%04x" <$> bs)
where
bs = reverse $ dropWhile (== 0) [b4, b3, b2, b1]
b4 = takeBits 16 gap
b3 = takeBits 16 (shiftR gap 16)
b2 = takeBits 16 (shiftR gap 32)
b1 = takeBits 16 (shiftR gap 48)
takeBits :: Int -> Word64 -> Word64
takeBits wid wor = wor .&. (shiftL 1 wid - 1)
-- Conversion Lenses -----------------------------------------------------------
2019-05-08 21:47:20 +03:00
diffTime :: Iso' Gap DiffTime
diffTime = iso fromGap toGap
where
fromGap = picosecondsToDiffTime . view picoSecs
toGap = view (from picoSecs) . diffTimeToPicoseconds
sysUTC :: Iso' SystemTime UTCTime
sysUTC = iso systemToUTCTime utcToSystemTime
2019-05-08 21:47:20 +03:00
utcTime :: Iso' Wen UTCTime
utcTime = systemTime . sysUTC
unixEpoch :: Wen
unixEpoch = Wen (Gap 0x8000_000c_ce9e_0d80_0000_0000_0000_0000)
2019-05-08 21:47:20 +03:00
unixSystemTime :: Iso' Unix SystemTime
unixSystemTime = iso toSys fromSys
2019-05-08 21:47:20 +03:00
where
toSys (Unix gap) = MkSystemTime (fromInteger sec) (fromInteger ns)
where (sec, ns) = quotRem (gap ^. nanoSecs) 1_000_000_000
fromSys (MkSystemTime sec ns) =
Unix $ (toInteger sec ^. from secs)
+ (toInteger ns ^. from nanoSecs)
2019-05-08 21:47:20 +03:00
unix :: Iso' Wen Unix
unix = iso toUnix fromUnix
where
toUnix (Wen g) = Unix (g - unWen unixEpoch)
fromUnix (Unix g) = Wen (unWen unixEpoch + g)
unWen (Wen x) = x
2019-05-08 21:47:20 +03:00
systemTime :: Iso' Wen SystemTime
systemTime = unix . unixSystemTime
2019-05-08 21:47:20 +03:00
--------------------------------------------------------------------------------
2019-05-08 21:47:20 +03:00
toDenomSecs :: Integer -> Gap -> Integer
toDenomSecs denom (Gap g) = shiftR (g * denom) 64
2019-05-08 21:47:20 +03:00
fromDenomSecs :: Integer -> Integer -> Gap
fromDenomSecs denom ds =
Gap $ (shiftL ds 64) `div` denom
2019-05-08 21:47:20 +03:00
picoSecs :: Iso' Gap Integer
picoSecs = iso (toDenomSecs denom) (fromDenomSecs denom)
where denom = 1_000_000_000_000
2019-05-08 21:47:20 +03:00
nanoSecs :: Iso' Gap Integer
nanoSecs = iso (toDenomSecs denom) (fromDenomSecs denom)
where denom = 1_000_000_000
2019-05-08 21:47:20 +03:00
microSecs :: Iso' Gap Integer
microSecs = iso (toDenomSecs denom) (fromDenomSecs denom)
where denom = 1_000_000
2019-05-08 21:47:20 +03:00
milliSecs :: Iso' Gap Integer
milliSecs = iso (toDenomSecs denom) (fromDenomSecs denom)
where denom = 1_000
secs :: Iso' Gap Integer
secs = iso (toDenomSecs denom) (fromDenomSecs denom)
where denom = 1
2019-05-08 21:47:20 +03:00
--------------------------------------------------------------------------------
now :: IO Wen
now = view (from systemTime) <$> getSystemTime
2019-05-08 21:47:20 +03:00
gap :: Wen -> Wen -> Gap
gap (Wen x) (Wen y) | x > y = x - y
| otherwise = y - x
2019-05-08 21:47:20 +03:00
addGap :: Wen -> Gap -> Wen
addGap (Wen x) y = Wen (x+y)