module Data.Time.Hora.Timestamp
(
now, now',
t, tf,
dt,
d, d') where
import Data.Time.Clock
import Data.Time.Hora.Format
import Data.Time.Hora.Type.DatePart
import Data.Time.Hora.Type.Time
import Data.Time.Hora.Parse
import Data.Time.LocalTime as L
now::Num a => IO (DatePart a)
now = withUTCTime parse
now'::Num a => IO (Tz (DatePart a))
now' = withTimeZone parse'
tf::IO String
tf = do
utc0 <- getCurrentTime
pure $ formatUTCTime "%T%Q" utc0
t::IO String
t = do
utc0 <- getCurrentTime
pure $ formatUTCTime "%T" utc0
dt::IO String
dt = do
utc0 <- getCurrentTime
pure $ formatUTCTime "%F %T" utc0
d::IO String
d = withUTCTime ymd
d'::IO (Tz String)
d' = withTimeZone ymd'
type WithLocalTimeZone a = TimeZone -> UTCTime -> Tz a
type WithUTCTime a = UTCTime -> a
withTimeZone::WithLocalTimeZone a -> IO (Tz a)
withTimeZone fn0 = do
z1 <- getCurrentTimeZone
t1 <- getCurrentTime
pure $ fn0 z1 t1
withUTCTime::WithUTCTime a -> IO a
withUTCTime fn0 = do
t1 <- getCurrentTime
pure $ fn0 t1