Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data types for representing different date and time-related information.
Internally, the types Int
and Int64
are used to
represent everything. These are used even when negative
values are not appropriate and even if a smaller fixed-size
integer could hold the information. The only cases when
Int64
is used are when it is neccessary to represent values
with numbers 2^29
or higher. These are typically fields
that represent nanoseconds.
Unlike the types in the venerable time
library, the types
here do not allow the user to work with all dates. Since this
library uses fixed-precision integral values instead of Integer
,
all of the usual problems with overflow should be considered. Notably,
PosixTime
and TaiTime
can only be used to represent time between the years
1680 and 2260. All other types in this library correctly represent time
a million years before or after 1970.
The vector unbox instances store
data in a reasonably compact manner. For example, the instance
for Day
has three unboxed vectors: Int
for the year, Int8
for the month, and Int8
for the day. This only causes
corruption of data if the user is trying to use out-of-bounds
values for the month and the day. Users are advised to not
use the data types provided here to model non-existent times.
Synopsis
- newtype Day = Day {}
- newtype DayOfWeek = DayOfWeek {
- getDayOfWeek :: Int
- newtype DayOfMonth = DayOfMonth {
- getDayOfMonth :: Int
- newtype DayOfYear = DayOfYear {
- getDayOfYear :: Int
- newtype Month = Month {}
- newtype Year = Year {}
- newtype Offset = Offset {}
- newtype Time = Time {}
- newtype DayOfWeekMatch a = DayOfWeekMatch {
- getDayOfWeekMatch :: Vector a
- newtype MonthMatch a = MonthMatch {
- getMonthMatch :: Vector a
- newtype UnboxedMonthMatch a = UnboxedMonthMatch {}
- newtype Timespan = Timespan {
- getTimespan :: Int64
- data SubsecondPrecision
- data Date = Date {}
- data OrdinalDate = OrdinalDate {}
- data MonthDate = MonthDate {}
- data Datetime = Datetime {
- datetimeDate :: !Date
- datetimeTime :: !TimeOfDay
- data OffsetDatetime = OffsetDatetime {}
- data TimeOfDay = TimeOfDay {
- timeOfDayHour :: !Int
- timeOfDayMinute :: !Int
- timeOfDayNanoseconds :: !Int64
- data DatetimeFormat = DatetimeFormat {}
- data OffsetFormat
- data DatetimeLocale a = DatetimeLocale {}
- data MeridiemLocale a = MeridiemLocale {
- meridiemLocaleAm :: !a
- meridiemLocalePm :: !a
- data TimeInterval = TimeInterval !Time !Time
- data TimeParts = TimeParts {
- timePartsDay :: !Int
- timePartsMonth :: !Int
- timePartsYear :: !Int
- timePartsHour :: !Int
- timePartsMinute :: !Int
- timePartsSecond :: !Int
- timePartsSubsecond :: !Int
- timePartsOffset :: !Int
Documentation
A day represented as the modified Julian date, the number of days since midnight on November 17, 1858.
Instances
FromJSON Day Source # | |
ToJSON Day Source # | |
Storable Day Source # | |
Enum Day Source # | |
Read Day Source # | |
Show Day Source # | |
NFData Day Source # | |
Eq Day Source # | |
Ord Day Source # | |
Hashable Day Source # | |
Prim Day Source # | |
Defined in Chronos alignment# :: Day -> Int# # indexByteArray# :: ByteArray# -> Int# -> Day # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Day #) # writeByteArray# :: MutableByteArray# s -> Int# -> Day -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Day -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Day # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Day #) # writeOffAddr# :: Addr# -> Int# -> Day -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Day -> State# s -> State# s # | |
Torsor Day Int Source # | |
The day of the week.
newtype DayOfMonth Source #
The day of the month.
Instances
The day of the year.
Instances
Read DayOfYear Source # | |
Show DayOfYear Source # | |
NFData DayOfYear Source # | |
Eq DayOfYear Source # | |
Ord DayOfYear Source # | |
Defined in Chronos | |
Prim DayOfYear Source # | |
Defined in Chronos sizeOf# :: DayOfYear -> Int# # alignment# :: DayOfYear -> Int# # indexByteArray# :: ByteArray# -> Int# -> DayOfYear # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, DayOfYear #) # writeByteArray# :: MutableByteArray# s -> Int# -> DayOfYear -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> DayOfYear -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> DayOfYear # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, DayOfYear #) # writeOffAddr# :: Addr# -> Int# -> DayOfYear -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> DayOfYear -> State# s -> State# s # |
The month of the year.
Instances
The number of years elapsed since the beginning of the Common Era.
A UTC offset.
Instances
FromJSON Offset Source # | |
FromJSONKey Offset Source # | |
Defined in Chronos | |
ToJSON Offset Source # | |
ToJSONKey Offset Source # | |
Defined in Chronos | |
Enum Offset Source # | |
Defined in Chronos | |
Read Offset Source # | |
Show Offset Source # | |
NFData Offset Source # | |
Eq Offset Source # | |
Ord Offset Source # | |
Torsor Offset Int Source # | |
POSIX time with nanosecond resolution.
Instances
FromJSON Time Source # | |
ToJSON Time Source # | |
Storable Time Source # | |
Defined in Chronos | |
Bounded Time Source # | |
Read Time Source # | |
Show Time Source # | |
NFData Time Source # | |
Eq Time Source # | |
Ord Time Source # | |
Hashable Time Source # | |
Prim Time Source # | |
Defined in Chronos alignment# :: Time -> Int# # indexByteArray# :: ByteArray# -> Int# -> Time # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Time #) # writeByteArray# :: MutableByteArray# s -> Int# -> Time -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Time -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Time # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Time #) # writeOffAddr# :: Addr# -> Int# -> Time -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Time -> State# s -> State# s # | |
Torsor Time Timespan Source # | |
newtype DayOfWeekMatch a Source #
Match a DayOfWeek
. By match
, we mean that a DayOfWeekMatch
is a mapping from the integer value of a DayOfWeek
to some value
of type a
. You should construct a DayOfWeekMatch
with
buildDayOfWeekMatch
, and match it using caseDayOfWeek
.
Instances
NFData a => NFData (DayOfWeekMatch a) Source # | |
Defined in Chronos rnf :: DayOfWeekMatch a -> () # |
newtype MonthMatch a Source #
Match a Month
. By match
, we mean that a MonthMatch
is
a mapping from the integer value of a Month
to some value of
type a
. You should construct a MonthMatch
with
buildMonthMatch
, and match it using caseMonth
.
Instances
NFData a => NFData (MonthMatch a) Source # | |
Defined in Chronos rnf :: MonthMatch a -> () # |
newtype UnboxedMonthMatch a Source #
Like MonthMatch
, but the matched value can have an instance of
Unbox
.
Instances
NFData (UnboxedMonthMatch a) Source # | |
Defined in Chronos rnf :: UnboxedMonthMatch a -> () # |
A timespan. This is represented internally as a number of nanoseconds.
Instances
data SubsecondPrecision Source #
The precision used when encoding seconds to a human-readable format.
SubsecondPrecisionAuto | Rounds to second, millisecond, microsecond, or nanosecond |
SubsecondPrecisionFixed !Int | Specify number of places after decimal |
Instances
Read SubsecondPrecision Source # | |
Defined in Chronos | |
Show SubsecondPrecision Source # | |
Defined in Chronos showsPrec :: Int -> SubsecondPrecision -> ShowS # show :: SubsecondPrecision -> String # showList :: [SubsecondPrecision] -> ShowS # | |
NFData SubsecondPrecision Source # | |
Defined in Chronos rnf :: SubsecondPrecision -> () # | |
Eq SubsecondPrecision Source # | |
Defined in Chronos (==) :: SubsecondPrecision -> SubsecondPrecision -> Bool # (/=) :: SubsecondPrecision -> SubsecondPrecision -> Bool # | |
Ord SubsecondPrecision Source # | |
Defined in Chronos compare :: SubsecondPrecision -> SubsecondPrecision -> Ordering # (<) :: SubsecondPrecision -> SubsecondPrecision -> Bool # (<=) :: SubsecondPrecision -> SubsecondPrecision -> Bool # (>) :: SubsecondPrecision -> SubsecondPrecision -> Bool # (>=) :: SubsecondPrecision -> SubsecondPrecision -> Bool # max :: SubsecondPrecision -> SubsecondPrecision -> SubsecondPrecision # min :: SubsecondPrecision -> SubsecondPrecision -> SubsecondPrecision # |
A date as represented by the Gregorian calendar.
data OrdinalDate Source #
An OrdinalDate
is a Year
and the number of days elapsed
since the Year
began.
Instances
A month and the day of the month. This does not actually represent a specific date, since this recurs every year.
A Date
as represented by the Gregorian calendar
and a TimeOfDay
.
While the ToJSON
instance encodes with a hyphen separator, the
FromJSON
instance allows any non-digit character to act as
separator, using the lenient parser.
Datetime | |
|
data OffsetDatetime Source #
Instances
Read OffsetDatetime Source # | |
Defined in Chronos readsPrec :: Int -> ReadS OffsetDatetime # readList :: ReadS [OffsetDatetime] # | |
Show OffsetDatetime Source # | |
Defined in Chronos showsPrec :: Int -> OffsetDatetime -> ShowS # show :: OffsetDatetime -> String # showList :: [OffsetDatetime] -> ShowS # | |
NFData OffsetDatetime Source # | |
Defined in Chronos rnf :: OffsetDatetime -> () # | |
Eq OffsetDatetime Source # | |
Defined in Chronos (==) :: OffsetDatetime -> OffsetDatetime -> Bool # (/=) :: OffsetDatetime -> OffsetDatetime -> Bool # | |
Ord OffsetDatetime Source # | |
Defined in Chronos compare :: OffsetDatetime -> OffsetDatetime -> Ordering # (<) :: OffsetDatetime -> OffsetDatetime -> Bool # (<=) :: OffsetDatetime -> OffsetDatetime -> Bool # (>) :: OffsetDatetime -> OffsetDatetime -> Bool # (>=) :: OffsetDatetime -> OffsetDatetime -> Bool # max :: OffsetDatetime -> OffsetDatetime -> OffsetDatetime # min :: OffsetDatetime -> OffsetDatetime -> OffsetDatetime # |
A time of day with nanosecond resolution.
TimeOfDay | |
|
data DatetimeFormat Source #
The format of a Datetime
. In particular
this provides separators for parts of the Datetime
and nothing else.
DatetimeFormat | |
|
Instances
Read DatetimeFormat Source # | |
Defined in Chronos readsPrec :: Int -> ReadS DatetimeFormat # readList :: ReadS [DatetimeFormat] # | |
Show DatetimeFormat Source # | |
Defined in Chronos showsPrec :: Int -> DatetimeFormat -> ShowS # show :: DatetimeFormat -> String # showList :: [DatetimeFormat] -> ShowS # | |
NFData DatetimeFormat Source # | |
Defined in Chronos rnf :: DatetimeFormat -> () # | |
Eq DatetimeFormat Source # | |
Defined in Chronos (==) :: DatetimeFormat -> DatetimeFormat -> Bool # (/=) :: DatetimeFormat -> DatetimeFormat -> Bool # | |
Ord DatetimeFormat Source # | |
Defined in Chronos compare :: DatetimeFormat -> DatetimeFormat -> Ordering # (<) :: DatetimeFormat -> DatetimeFormat -> Bool # (<=) :: DatetimeFormat -> DatetimeFormat -> Bool # (>) :: DatetimeFormat -> DatetimeFormat -> Bool # (>=) :: DatetimeFormat -> DatetimeFormat -> Bool # max :: DatetimeFormat -> DatetimeFormat -> DatetimeFormat # min :: DatetimeFormat -> DatetimeFormat -> DatetimeFormat # |
data OffsetFormat Source #
Formatting settings for a timezone offset.
OffsetFormatColonOff |
|
OffsetFormatColonOn |
|
OffsetFormatSecondsPrecision |
|
OffsetFormatColonAuto |
|
Instances
data DatetimeLocale a Source #
Locale-specific formatting for weekdays and months. The
type variable will likely be instantiated to Text
or ByteString
.
DatetimeLocale | |
|
Instances
NFData a => NFData (DatetimeLocale a) Source # | |
Defined in Chronos rnf :: DatetimeLocale a -> () # |
data MeridiemLocale a Source #
Locale-specific formatting for AM and PM.
MeridiemLocale | |
|
Instances
data TimeInterval Source #
A TimeInterval represents a start and end time.
It can sometimes be more ergonomic than the Torsor
API when
you only care about whether or not a Time
is within a certain range.
To construct a TimeInterval
, it is best to use timeIntervalBuilder
,
which maintains the invariant that
(all functions that act on lowerBound
interval <=
upperBound
intervalTimeInterval
s assume this invariant).
Instances
Bounded TimeInterval Source # | |
Defined in Chronos | |
Read TimeInterval Source # | |
Defined in Chronos readsPrec :: Int -> ReadS TimeInterval # readList :: ReadS [TimeInterval] # | |
Show TimeInterval Source # | |
Defined in Chronos showsPrec :: Int -> TimeInterval -> ShowS # show :: TimeInterval -> String # showList :: [TimeInterval] -> ShowS # | |
NFData TimeInterval Source # | |
Defined in Chronos rnf :: TimeInterval -> () # | |
Eq TimeInterval Source # | |
Defined in Chronos (==) :: TimeInterval -> TimeInterval -> Bool # (/=) :: TimeInterval -> TimeInterval -> Bool # | |
Ord TimeInterval Source # | |
Defined in Chronos compare :: TimeInterval -> TimeInterval -> Ordering # (<) :: TimeInterval -> TimeInterval -> Bool # (<=) :: TimeInterval -> TimeInterval -> Bool # (>) :: TimeInterval -> TimeInterval -> Bool # (>=) :: TimeInterval -> TimeInterval -> Bool # max :: TimeInterval -> TimeInterval -> TimeInterval # min :: TimeInterval -> TimeInterval -> TimeInterval # |
Holds all of the parts encoded by a Time
.
Can be used for formatting if what is presently in the API
does not suffice.
TimeParts | |
|