thyme-0.4: A faster time library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Thyme.LocalTime

Description

Local time and time zones.

Synopsis

Documentation

type Hour = Int Source #

Hour time-of-day.

type Minute = Int Source #

Minute time-of-day.

data TimeOfDay Source #

Time of day in hour, minute, second.

Constructors

TimeOfDay 

Fields

Instances

Instances details
Arbitrary TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

CoArbitrary TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

coarbitrary :: TimeOfDay -> Gen b -> Gen b #

Data TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay #

toConstr :: TimeOfDay -> Constr #

dataTypeOf :: TimeOfDay -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) #

gmapT :: (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeOfDay -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

Bounded TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Generic TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Associated Types

type Rep TimeOfDay :: Type -> Type #

Read TimeOfDay Source # 
Instance details

Defined in Data.Thyme.Format

Show TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

NFData TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

rnf :: TimeOfDay -> () #

Eq TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Ord TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Hashable TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Random TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

randomR :: RandomGen g => (TimeOfDay, TimeOfDay) -> g -> (TimeOfDay, g) #

random :: RandomGen g => g -> (TimeOfDay, g) #

randomRs :: RandomGen g => (TimeOfDay, TimeOfDay) -> g -> [TimeOfDay] #

randoms :: RandomGen g => g -> [TimeOfDay] #

FormatTime TimeOfDay Source # 
Instance details

Defined in Data.Thyme.Format

ParseTime TimeOfDay Source # 
Instance details

Defined in Data.Thyme.Format

Unbox TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

Thyme TimeOfDay TimeOfDay Source # 
Instance details

Defined in Data.Thyme.Time.Core

Vector Vector TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

MVector MVector TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

type Rep TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

type Rep TimeOfDay = D1 ('MetaData "TimeOfDay" "Data.Thyme.LocalTime" "thyme-0.4-HyK6SfK4MlBKX4LjgMsZJ4" 'False) (C1 ('MetaCons "TimeOfDay" 'PrefixI 'True) (S1 ('MetaSel ('Just "todHour") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Hour) :*: (S1 ('MetaSel ('Just "todMin") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Minute) :*: S1 ('MetaSel ('Just "todSec") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 DiffTime))))
newtype Vector TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

newtype MVector s TimeOfDay Source # 
Instance details

Defined in Data.Thyme.LocalTime

data TimeZone Source #

Description of one time zone.

A TimeZone is a whole number of minutes offset from UTC, together with a name and a ‘summer time’ flag.

Constructors

TimeZone 

Fields

Instances

Instances details
Arbitrary TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

CoArbitrary TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

coarbitrary :: TimeZone -> Gen b -> Gen b #

Data TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeZone -> c TimeZone #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeZone #

toConstr :: TimeZone -> Constr #

dataTypeOf :: TimeZone -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeZone) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone) #

gmapT :: (forall b. Data b => b -> b) -> TimeZone -> TimeZone #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeZone -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeZone -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone #

Bounded TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Generic TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Associated Types

type Rep TimeZone :: Type -> Type #

Methods

from :: TimeZone -> Rep TimeZone x #

to :: Rep TimeZone x -> TimeZone #

Show TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

NFData TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

rnf :: TimeZone -> () #

Eq TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Ord TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Hashable TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

hashWithSalt :: Int -> TimeZone -> Int #

hash :: TimeZone -> Int #

Random TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

randomR :: RandomGen g => (TimeZone, TimeZone) -> g -> (TimeZone, g) #

random :: RandomGen g => g -> (TimeZone, g) #

randomRs :: RandomGen g => (TimeZone, TimeZone) -> g -> [TimeZone] #

randoms :: RandomGen g => g -> [TimeZone] #

FormatTime TimeZone Source # 
Instance details

Defined in Data.Thyme.Format

Methods

showsTime :: TimeLocale -> TimeZone -> (Char -> ShowS) -> Char -> ShowS Source #

ParseTime TimeZone Source # 
Instance details

Defined in Data.Thyme.Format

Thyme TimeZone TimeZone Source # 
Instance details

Defined in Data.Thyme.Time.Core

type Rep TimeZone Source # 
Instance details

Defined in Data.Thyme.LocalTime

type Rep TimeZone = D1 ('MetaData "TimeZone" "Data.Thyme.LocalTime" "thyme-0.4-HyK6SfK4MlBKX4LjgMsZJ4" 'False) (C1 ('MetaCons "TimeZone" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeZoneMinutes") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Minutes) :*: (S1 ('MetaSel ('Just "timeZoneSummerOnly") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "timeZoneName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

type Minutes = Int Source #

Minutes duration.

type Hours = Int Source #

Hours duration.

timeZoneOffsetString :: TimeZone -> String Source #

Text representing the offset of this timezone, e.g. "-0800" or "+0400" (like %z in formatTime)

timeZoneOffsetStringColon :: TimeZone -> String Source #

Text representing the offset of this timezone in ISO 8601 style, e.g. "-08:00" or "+04:00" (like %N in formatTime)

minutesToTimeZone :: Minutes -> TimeZone Source #

Create a nameless non-summer timezone for this number of minutes

hoursToTimeZone :: Hours -> TimeZone Source #

Create a nameless non-summer timezone for this number of hours

utc :: TimeZone Source #

The UTC (Zulu) time zone.

utc = TimeZone 0 False "UTC"

getTimeZone :: UTCTime -> IO TimeZone Source #

Get the local time zone at the given time, varying as per summer time adjustments.

Performed by localtime_r or a similar call.

data LocalTime Source #

Local calendar date and time-of-day.

This type is appropriate for inputting from and outputting to the outside world.

To actually perform logic and arithmetic on local date-times, a LocalTime should first be converted to a UTCTime by the utcLocalTime Iso.

See also: ZonedTime.

Constructors

LocalTime 

Fields

Instances

Instances details
Arbitrary LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

CoArbitrary LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

coarbitrary :: LocalTime -> Gen b -> Gen b #

Data LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalTime -> c LocalTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalTime #

toConstr :: LocalTime -> Constr #

dataTypeOf :: LocalTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LocalTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalTime) #

gmapT :: (forall b. Data b => b -> b) -> LocalTime -> LocalTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

Bounded LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Generic LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Associated Types

type Rep LocalTime :: Type -> Type #

Read LocalTime Source # 
Instance details

Defined in Data.Thyme.Format

Show LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

NFData LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

rnf :: LocalTime -> () #

Eq LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Ord LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Hashable LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Random LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

randomR :: RandomGen g => (LocalTime, LocalTime) -> g -> (LocalTime, g) #

random :: RandomGen g => g -> (LocalTime, g) #

randomRs :: RandomGen g => (LocalTime, LocalTime) -> g -> [LocalTime] #

randoms :: RandomGen g => g -> [LocalTime] #

FormatTime LocalTime Source # 
Instance details

Defined in Data.Thyme.Format

ParseTime LocalTime Source # 
Instance details

Defined in Data.Thyme.Format

Unbox LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Thyme LocalTime LocalTime Source # 
Instance details

Defined in Data.Thyme.Time.Core

Vector Vector LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

MVector MVector LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

type Rep LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

type Rep LocalTime = D1 ('MetaData "LocalTime" "Data.Thyme.LocalTime" "thyme-0.4-HyK6SfK4MlBKX4LjgMsZJ4" 'False) (C1 ('MetaCons "LocalTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "localDay") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Day) :*: S1 ('MetaSel ('Just "localTimeOfDay") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 TimeOfDay)))
newtype Vector LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

newtype MVector s LocalTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

minuteLength :: Hour -> Minute -> DiffTime Source #

The maximum possible length of a minute. Always 60s, except at 23:59 due to leap seconds.

minuteLength 23 59 = fromSeconds' 61
minuteLength _  _  = fromSeconds' 60

midnight :: TimeOfDay Source #

Hour zero, midnight.

midnight = TimeOfDay 0 0 zeroV

midday :: TimeOfDay Source #

Hour twelve, noon.

midday = TimeOfDay 12 0 zeroV

makeTimeOfDayValid :: Hour -> Minute -> DiffTime -> Maybe TimeOfDay Source #

Construct a TimeOfDay from the hour, minute, and second.

Returns Nothing if these constraints are not satisfied:

  • 0 ≤ hour ≤ 23
  • 0 ≤ minute ≤ 59
  • 0 ≤ second < minuteLength hour minute

timeOfDay :: Iso' DiffTime TimeOfDay Source #

Conversion between DiffTime and TimeOfDay.

> fromSeconds' 100 ^. timeOfDay
00:01:40

> timeOfDay # TimeOfDay 0 1 40
100s

addMinutes :: Minutes -> TimeOfDay -> (Days, TimeOfDay) Source #

Add some minutes to a TimeOfDay; the result includes a day adjustment.

> addMinutes 10 (TimeOfDay 23 55 0)
(1,00:05:00)

dayFraction :: Iso' TimeOfDay Rational Source #

Conversion between TimeOfDay and the fraction of a day.

> TimeOfDay 6 0 0 ^. dayFraction
1 % 4
> TimeOfDay 8 0 0 ^. dayFraction
1 % 3

> dayFraction # (1 / 4)
06:00:00
> dayFraction # (1 / 3)
08:00:00

data ZonedTime Source #

A LocalTime and its TimeZone.

This type is appropriate for inputting from and outputting to the outside world.

To actually perform logic and arithmetic on local date-times, a ZonedTime should first be converted to a UTCTime by the zonedTime Iso.

Instances

Instances details
Arbitrary ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

CoArbitrary ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

coarbitrary :: ZonedTime -> Gen b -> Gen b #

FromJSON ZonedTime Source # 
Instance details

Defined in Data.Thyme.Format.Aeson

ToJSON ZonedTime Source # 
Instance details

Defined in Data.Thyme.Format.Aeson

Data ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZonedTime -> c ZonedTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZonedTime #

toConstr :: ZonedTime -> Constr #

dataTypeOf :: ZonedTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZonedTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZonedTime) #

gmapT :: (forall b. Data b => b -> b) -> ZonedTime -> ZonedTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> ZonedTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ZonedTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime #

Bounded ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Generic ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Associated Types

type Rep ZonedTime :: Type -> Type #

Read ZonedTime Source # 
Instance details

Defined in Data.Thyme.Format

Show ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

NFData ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

rnf :: ZonedTime -> () #

Eq ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Ord ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Hashable ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Random ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

Methods

randomR :: RandomGen g => (ZonedTime, ZonedTime) -> g -> (ZonedTime, g) #

random :: RandomGen g => g -> (ZonedTime, g) #

randomRs :: RandomGen g => (ZonedTime, ZonedTime) -> g -> [ZonedTime] #

randoms :: RandomGen g => g -> [ZonedTime] #

FormatTime ZonedTime Source # 
Instance details

Defined in Data.Thyme.Format

ParseTime ZonedTime Source # 
Instance details

Defined in Data.Thyme.Format

Thyme ZonedTime ZonedTime Source # 
Instance details

Defined in Data.Thyme.Time.Core

type Rep ZonedTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

type Rep ZonedTime = D1 ('MetaData "ZonedTime" "Data.Thyme.LocalTime" "thyme-0.4-HyK6SfK4MlBKX4LjgMsZJ4" 'False) (C1 ('MetaCons "ZonedTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "zonedTimeToLocalTime") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 LocalTime) :*: S1 ('MetaSel ('Just "zonedTimeZone") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimeZone)))

utcLocalTime :: TimeZone -> Iso' UTCTime LocalTime Source #

Conversion between UTCTime and LocalTime.

> tz <- getCurrentTimeZone

> timeZoneName tz
"JST"

> timeZoneOffsetString tz
"+0900"

> now <- getCurrentTime
> now
2016-04-23 02:00:00.000000 UTC

> let local = now ^. utcLocalTime tz
> local
2016-04-23 11:00:00.000000

> utcLocalTime tz # local
2016-04-23 02:00:00.000000 UTC

See also: zonedTime.

zonedTime :: Iso' (TimeZone, UTCTime) ZonedTime Source #

Conversion between (TimeZone, UTCTime) and ZonedTime.

> now <- getZonedTime
> now
2016-04-04 16:00:00.000000 JST

> zonedTime # now
(JST,2016-04-04 07:00:00.000000 UTC)

> (zonedTime # now) ^. zonedTime
2016-04-04 16:00:00.000000 JST

See also: utcLocalTime.

getZonedTime :: IO ZonedTime Source #

Get the current local date, time, and time zone.

> getZonedTime
2016-04-23 11:57:22.516064 JST

See also: getCurrentTime, getPOSIXTime.

utcToLocalZonedTime :: UTCTime -> IO ZonedTime Source #

Convert a UTCTime to a ZonedTime according to the local time zone returned by getTimeZone.

See also: zonedTime.

utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Days, TimeOfDay) Source #

Convert a UTC TimeOfDay to a TimeOfDay in some timezone, together with a day adjustment.

utcToLocalTimeOfDay = addMinutes . timeZoneMinutes

localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Days, TimeOfDay) Source #

Convert a TimeOfDay in some timezone to a UTC TimeOfDay, together with a day adjustment.

localToUTCTimeOfDay = addMinutes . negate . timeZoneMinutes

timeToTimeOfDay :: DiffTime -> TimeOfDay Source #

Convert a DiffTime of the duration since midnight to a TimeOfDay. Durations exceeding 24 hours will be treated as leap-seconds.

timeToTimeOfDay = view timeOfDay
timeToTimeOfDay d ≡ d ^. timeOfDay

timeOfDayToTime :: TimeOfDay -> DiffTime Source #

Convert a TimeOfDay to a DiffTime of the duration since midnight. TimeOfDay greater than 24 hours will be treated as leap-seconds.

timeOfDayToTime = review timeOfDay
timeOfDayToTime tod ≡ timeOfDay # tod

dayFractionToTimeOfDay :: Rational -> TimeOfDay Source #

Convert a fraction of a day since midnight to a TimeOfDay.

dayFractionToTimeOfDay = review dayFraction

timeOfDayToDayFraction :: TimeOfDay -> Rational Source #

Convert a TimeOfDay to a fraction of a day since midnight.

timeOfDayToDayFraction = view dayFraction

ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime Source #

Convert a UniversalTime to a LocalTime at the given medidian in degrees East.

ut1ToLocalTime = view . ut1LocalTime

localTimeToUT1 :: Rational -> LocalTime -> UniversalTime Source #

Convert a LocalTime at the given meridian in degrees East to a UniversalTime.

localTimeToUT1 = review . ut1LocalTime

utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime Source #

Convert a UTCTime and the given TimeZone into a ZonedTime.

utcToZonedTime z t = view zonedTime (z, t)

Orphan instances

Show UTCTime Source # 
Instance details