hodatime-0.1.1.1: A fully featured date/time library based on Nodatime

Copyright(C) 2016 Jason Johnson
LicenseBSD-style (see the file LICENSE)
MaintainerJason Johnson <jason.johnson.081@gmail.com>
Stabilityexperimental
PortabilityTBD
Safe HaskellSafe
LanguageHaskell2010

Data.HodaTime.Instant

Contents

Description

An Instant is universal fixed moment in time.

Synopsis

Types

data Instant Source #

Represents a point on a global time line. An Instant has no concept of time zone or calendar. It is nothing more than the number of nanoseconds since epoch (1.March.2000)

Constructors

fromSecondsSinceUnixEpoch :: Int -> Instant Source #

Create an Instant from an Int that represents a Unix Epoch

now :: IO Instant Source #

Create an Instant from the current system time

Math

add :: Instant -> Duration -> Instant Source #

Add a Duration to an Instant to get a future Instant. NOTE: does not handle all negative durations, use minus

difference :: Instant -> Instant -> Duration Source #

Get the difference between two instances

minus :: Instant -> Duration -> Instant Source #

} -- | Create an OffsetDateTime from this Instant and an Offset withOffset :: Instant -> Offset -> Calendar -> OffsetDateTime withOffset instant offset calendar = OffsetDateTime (LocalDateTime date time) offset -- TODO: I'm not sure I like applying the offset on construction. See if we can defer it where instant' = instant add (D.fromSeconds . fromIntegral . offsetSeconds $ offset) time = LTI.fromInstant instant' date | calendar == Gregorian || calendar == Iso = GI.fromInstantInCalendar instant' calendar | otherwise = undefined -- TODO: Why does compiler think this isn't total without the otherwise?

  • - | Convert Instant Into a ZonedDateTime based on the supplied TimeZone and Calendar inZone :: Instant -> TimeZone -> Calendar -> ZonedDateTime inZone instant UTCzone calendar = ZonedDateTime odt UTCzone where odt = withOffset instant Offset.empty calendar inZone instant tzi@TimeZone { } calendar = ZonedDateTime odt tzi where odt = withOffset instant offset calendar offset | otherwise = undefined -- TODO: When TimeZone module is implemented we can finish this (look at the olson time zone series from hackage, but we can't use it all)

Subtract a Duration from an Instant to get an Instant in the past. NOTE: does not handle negative durations, use add

Conversion

inUtc :: Instant -> ZonedDateTime Source #

Convert Instant to a ZonedDateTime in the UTC time zone, ISO calendar

Debug - to be removed