chronos-1.0.7: A performant time library

Safe HaskellNone
LanguageHaskell2010

Chronos

Contents

Description

Chronos is a performance-oriented time library for Haskell, with a straightforward API. The main differences between this and the time library are:

  • Chronos uses machine integers where possible. This means that time-related arithmetic should be faster, with the drawback that the types are incapable of representing times that are very far in the future or the past (because Chronos provides nanosecond, rather than picosecond, resolution). For most users, this is not a hindrance.
  • Chronos provides 'ToJSON'/'FromJSON' instances for serialisation.
  • Chronos provides Unbox instances for working with unboxed vectors.
  • Chronos provides Prim instances for working with byte arrays/primitive arrays.
  • Chronos uses normal non-overloaded haskell functions for encoding and decoding time. It provides attoparsec parsers for both Text and ByteString. Additionally, Chronos provides functions for encoding time to Text or ByteString. The http://hackage.haskell.org/package/time time> library accomplishes these with the Data.Time.Format module, which uses UNIX-style datetime format strings. The approach taken by Chronos is faster and catches more mistakes at compile time, at the cost of being less expressive.
Synopsis

Functions

Current

now :: IO Time Source #

Get the current time from the system clock.

today :: IO Day Source #

Gets the current Day. This does not take the user's time zone into account.

tomorrow :: IO Day Source #

Gets the Day of tomorrow.

yesterday :: IO Day Source #

Gets the Day of yesterday.

epoch :: Time Source #

The Unix epoch, that is 1970-01-01 00:00:00.

Duration

stopwatch :: IO a -> IO (Timespan, a) Source #

Measures the time it takes to run an action and evaluate its result to WHNF. This measurement uses a monotonic clock instead of the standard system clock.

stopwatch_ :: IO a -> IO Timespan Source #

Measures the time it takes to run an action. The result is discarded. This measurement uses a monotonic clock instead of the standard system clock.

stopwatchWith :: Clock -> IO a -> IO (Timespan, a) Source #

Variant of stopwatch that accepts a clock type. Users need to import System.Clock from the clock package in order to provide the clock type.

stopwatchWith_ :: Clock -> IO a -> IO Timespan Source #

Variant of stopwatch_ that accepts a clock type.

Construction

datetimeFromYmdhms Source #

Arguments

:: Int

Year

-> Int

Month

-> Int

Day

-> Int

Hour

-> Int

Minute

-> Int

Second

-> Datetime 

Construct a Datetime from year, month, day, hour, minute, second:

>>> datetimeFromYmdhms 2014 2 26 17 58 52
Datetime {datetimeDate = Date {dateYear = Year {getYear = 2014}, dateMonth = Month {getMonth = 1}, dateDay = DayOfMonth {getDayOfMonth = 26}}, datetimeTime = TimeOfDay {timeOfDayHour = 17, timeOfDayMinute = 58, timeOfDayNanoseconds = 52000000000}}

timeFromYmdhms Source #

Arguments

:: Int

Year

-> Int

Month

-> Int

Day

-> Int

Hour

-> Int

Minute

-> Int

Second

-> Time 

Construct a Time from year, month, day, hour, minute, second:

>>> timeFromYmdhms 2014 2 26 17 58 52
Time {getTime = 1393437532000000000}

Conversion

timeToDatetime :: Time -> Datetime Source #

Convert Time to Datetime.

\(t :: Time) -> (datetimeToTime (timeToDatetime t)) == t

datetimeToTime :: Datetime -> Time Source #

Convert Datetime to Time.

\(d :: Datetime) -> timeToDatetime (datetimeToTime d) == d

timeToDayTruncate :: Time -> Day Source #

Convert Time to Day. This function is lossy; consequently, it does not roundtrip with dayToTimeMidnight.

dayToTimeMidnight :: Day -> Time Source #

Convert midnight of the given Day to Time.

dayToDate :: Day -> Date Source #

Convert Day to a Date.

\(d :: Day) -> dateToDay (dayToDate d) == d

dateToDay :: Date -> Day Source #

Convert a Date to a Day.

\(d :: Date) -> dayToDate (dateToDay d) == d

monthDateToDayOfYear Source #

Arguments

:: Bool

Is it a leap year?

-> MonthDate 
-> DayOfYear 

Convert a MonthDate to a DayOfYear.

dayOfYearToMonthDay Source #

Arguments

:: Bool

Is it a leap year?

-> DayOfYear 
-> MonthDate 

Convert a DayOfYear to a MonthDate.

Build Timespan

second :: Timespan Source #

A Timespan representing a single second.

minute :: Timespan Source #

A Timespan representing a single minute.

hour :: Timespan Source #

A Timespan representing a single hour.

day :: Timespan Source #

A Timespan representing a single day.

week :: Timespan Source #

A Timespan representing a single week.

Matching

buildDayOfWeekMatch :: a -> a -> a -> a -> a -> a -> a -> DayOfWeekMatch a Source #

Build a DayOfWeekMatch from seven (7) values.

buildMonthMatch :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> MonthMatch a Source #

Build a MonthMatch from twelve (12) values.

buildUnboxedMonthMatch :: Unbox a => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> UnboxedMonthMatch a Source #

Build an UnboxedMonthMatch from twelve (12) values.

caseMonth :: MonthMatch a -> Month -> a Source #

Match a Month against a MonthMatch.

Format

The formats provided is this module are language-agnostic. To find meridiem formats and month formats, look in a language-specific module.

w3c :: DatetimeFormat Source #

The W3C DatetimeFormat.

>>> encode_YmdHMS SubsecondPrecisionAuto w3c (timeToDatetime (timeFromYmdhms 2014 2 26 17 58 52))
"2014-02-26T17:58:52"
\(s :: SubsecondPrecision) (dt :: Datetime) -> isJust (decode_YmdHMS w3c (encode_YmdHMS s w3c dt))

slash :: DatetimeFormat Source #

A DatetimeFormat that separates the members of the Date by slashes.

>>> encode_YmdHMS SubsecondPrecisionAuto slash (timeToDatetime (timeFromYmdhms 2014 2 26 17 58 52))
"2014/02/26 17:58:52"
\(s :: SubsecondPrecision) (dt :: Datetime) -> isJust (decode_YmdHMS slash (encode_YmdHMS s slash dt))

hyphen :: DatetimeFormat Source #

A DatetimeFormat that separates the members of the Date by hyphens.

>>> encode_YmdHMS SubsecondPrecisionAuto hyphen (timeToDatetime (timeFromYmdhms 2014 2 26 17 58 52))
"2014-02-26 17:58:52"
\(s :: SubsecondPrecision) (dt :: Datetime) -> isJust (decode_YmdHMS hyphen (encode_YmdHMS s hyphen dt))

compact :: DatetimeFormat Source #

A DatetimeFormat with no separators, except for a T between the Date and Time.

>>> encode_YmdHMS SubsecondPrecisionAuto compact (timeToDatetime (timeFromYmdhms 2014 2 26 17 58 52))
"20140226T175852"
\(s :: SubsecondPrecision) (dt :: Datetime) -> isJust (decode_YmdHMS compact (encode_YmdHMS s compact dt))

Months

january :: Month Source #

The Month of January.

february :: Month Source #

The Month of February.

march :: Month Source #

The Month of March.

april :: Month Source #

The Month of April.

may :: Month Source #

The Month of May.

june :: Month Source #

The Month of June.

july :: Month Source #

The Month of July.

august :: Month Source #

The Month of August.

september :: Month Source #

The Month of September.

october :: Month Source #

The Month of October.

november :: Month Source #

The Month of November.

december :: Month Source #

The Month of December.

Days of Week

Utility

daysInMonth Source #

Arguments

:: Bool

Is this a leap year?

-> Month

Month of year

-> Int 

Return the number of days in a given month.

isLeapYear :: Year -> Bool Source #

Is the Year a leap year?

>>> isLeapYear (Year 1996)
True
>>> isLeapYear (Year 2019)
False

Textual Conversion

Date

Text

builder_Ymd :: Maybe Char -> Date -> Builder Source #

Given a Date and a separator, construct a Text Builder corresponding to Year/Month/Day encoding.

builder_Dmy :: Maybe Char -> Date -> Builder Source #

Given a Date and a separator, construct a Text Builder corresponding to a Day/Month/Year encoding.

builder_HMS :: SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #

Given a SubsecondPrecision and a separator, construct a Text Builder corresponding to an Hour/Minute/Second encoding.

parser_Ymd :: Maybe Char -> Parser Date Source #

Parse a Year/Month/Day-encoded Date that uses the given separator.

parser_Mdy :: Maybe Char -> Parser Date Source #

Parse a Month/Day/Year-encoded Date that uses the given separator.

parser_Dmy :: Maybe Char -> Parser Date Source #

Parse a Day/Month/Year-encoded Date that uses the given separator.

UTF-8 ByteString

builderUtf8_Ymd :: Maybe Char -> Date -> Builder Source #

Given a Date and a separator, construct a ByteString Builder corresponding to a Day/Month/Year encoding.

parserUtf8_Ymd :: Maybe Char -> Parser Date Source #

Parse a Year/Month/Day-encoded Date that uses the given separator.

Time of Day

Text

builder_IMS_p :: MeridiemLocale Text -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a separator, construct a Text Builder according to an IMS encoding.

This differs from builder_IMSp in that their is a space between the seconds and locale.

builder_IMSp :: MeridiemLocale Text -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a separator, construct a Text Builder according to an IMS encoding.

parser_HMS :: Maybe Char -> Parser TimeOfDay Source #

Parse an Hour/Minute/Second-encoded TimeOfDay that uses the given separator.

parser_HMS_opt_S :: Maybe Char -> Parser TimeOfDay Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

UTF-8 ByteString

builderUtf8_HMS :: SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #

Given a SubsecondPrecision and a separator, construct a ByteString Builder corresponding to an Hour/Month/Second encoding of the given TimeOfDay.

builderUtf8_IMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a separator, construct a ByteString Builder corresponding to an IMS encoding of the given TimeOfDay. This differs from builderUtf8_IMSp in that there is a space between the seconds and locale.

builderUtf8_IMSp :: MeridiemLocale ByteString -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a separator, construct a ByteString Builder corresponding to an IMS encoding of the given TimeOfDay.

parserUtf8_HMS :: Maybe Char -> Parser TimeOfDay Source #

Parse an Hour/Minute/Second-encoded TimeOfDay that uses the given separator.

parserUtf8_HMS_opt_S :: Maybe Char -> Parser TimeOfDay Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

zeptoUtf8_HMS :: Maybe Char -> Parser TimeOfDay Source #

Parse a TimeOfDay that was encoded using the given separator.

Datetime

Text

builder_DmyHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a SubsecondPrecision and a DatetimeFormat, construct a Text Builder corresponding to a Day/Month/Year,Hour/Minute/Second encoding of the given Datetime.

builder_DmyIMSp :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct a Text Builder corresponding to a Day/Month/Year,IMS encoding of the given Datetime.

builder_DmyIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct a Text Builder corresponding to a Day/Month/Year,IMS encoding of the given Datetime. This differs from builder_DmyIMSp in that it adds a space between the locale and seconds.

builder_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a SubsecondPrecision and a DatetimeFormat, construct a Text Builder corresponding to a Year/Month/Day,Hour/Minute/Second encoding of the given Datetime.

builder_YmdIMSp :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct a Text Builder that corresponds to a Year/Month/Day,IMS encoding of the given Datetime.

builder_YmdIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct a Text Builder that corresponds to a Year/Month/Day,IMS encoding of the given Datetime. This inserts a space between the locale and seconds.

builderW3C :: Datetime -> Builder Source #

Construct a Text Builder corresponding to the W3C encoding of the given Datetime.

encode_DmyHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #

Given a SubsecondPrecision and DatetimeFormat, construct Text that corresponds to a Day/Month/Year,Hour/Minute/Second encoding of the given Datetime.

encode_DmyIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #

Given a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct Text that corresponds to a Day/Month/Year,IMS encoding of the given Datetime. This inserts a space between the locale and seconds.

encode_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #

Given a SubsecondPrecision and DatetimeFormat, construct Text that corresponds to a Year/Month/Day,Hour/Minute/Second encoding of the given Datetime.

encode_YmdIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #

Given a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct Text that corresponds to a Year/Month/Day,IMS encoding of the given Datetime. This inserts a space between the locale and seconds.

parser_DmyHMS :: DatetimeFormat -> Parser Datetime Source #

Parse a Day/Month/Year,Hour/Minute/Second-encoded Datetime that was encoded with the given DatetimeFormat.

parser_YmdHMS :: DatetimeFormat -> Parser Datetime Source #

Parses a Year/Month/Day,Hour/Minute/Second-encoded Datetime that was encoded using the given DatetimeFormat.

parser_YmdHMS_opt_S :: DatetimeFormat -> Parser Datetime Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

parser_DmyHMS_opt_S :: DatetimeFormat -> Parser Datetime Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

decode_DmyHMS :: DatetimeFormat -> Text -> Maybe Datetime Source #

Decode a Day/Month/Year,Hour/Minute/Second-encoded Datetime from Text that was encoded with the given DatetimeFormat.

decode_YmdHMS :: DatetimeFormat -> Text -> Maybe Datetime Source #

Decode a Year/Month/Day,Hour/Minute/Second-encoded Datetime from Text that was encoded with the given DatetimeFormat.

decode_YmdHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

decode_DmyHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

UTF-8 ByteString

encodeUtf8_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> ByteString Source #

Given a SubsecondPrecision and a DatetimeFormat, construct a ByteString corresponding to a Year/Month/Day,Hour/Minute/Second encoding of the given Datetime.

encodeUtf8_YmdIMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> ByteString Source #

Given a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct a ByteString corresponding to a Year/Month/Day,IMS encoding of the given Datetime. This inserts a space between the locale and seconds.

builderUtf8_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a SubsecondPrecision and a DatetimeFormat, construct a ByteString Builder corresponding to a Year/Month/Day,Hour/Minute/Second encoding of the given Datetime.

builderUtf8_YmdIMSp :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a SubsecondPrecision and a DatetimeFormat, construct a ByteString Builder corresponding to a Year/Month/Day,IMS encoding of the given Datetime.

builderUtf8_YmdIMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

Given a SubsecondPrecision and a DatetimeFormat, construct a ByteString Builder corresponding to a Year/Month/Day,IMS encoding of the given Datetime. This inserts a space between the locale and seconds.

builderUtf8W3C :: Datetime -> Builder Source #

Construct a ByteString Builder corresponding to a W3C encoding of the given Datetime.

decodeUtf8_YmdHMS :: DatetimeFormat -> ByteString -> Maybe Datetime Source #

Decode a Year/Month/Day,Hour/Minute/Second-encoded Datetime from a ByteString.

decodeUtf8_YmdHMS_opt_S :: DatetimeFormat -> ByteString -> Maybe Datetime Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

parserUtf8_YmdHMS :: DatetimeFormat -> Parser Datetime Source #

Parse a Year/Month/Day,Hour/Minute/Second-encoded Datetime that was encoded using the given DatetimeFormat.

parserUtf8_YmdHMS_opt_S :: DatetimeFormat -> Parser Datetime Source #

Parses text that is formatted as either of the following:

  • %H:%M
  • %H:%M:%S

That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. This format shows up in Google Chrome's datetime-local inputs.

zeptoUtf8_YmdHMS :: DatetimeFormat -> Parser Datetime Source #

Parse a Datetime that was encoded using the given DatetimeFormat.

Offset Datetime

Text

encode_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Text Source #

Given an OffsetFormat, a SubsecondPrecision, and a DatetimeFormat, construct Text corresponding to the Year/Month/Day,Hour/Minute/Second-encoding of the given OffsetDatetime.

encode_DmyHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Text Source #

Given an OffsetFormat, a SubsecondPrecision, and a DatetimeFormat, construct Text corresponding to the Day/Month/Year,Hour/Minute/Second encoding of the given OffsetDatetime.

builder_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #

Given an OffsetFormat, a SubsecondPrecision, and a DatetimeFormat, construct a Text Builder corresponding to a Year/Month/Day,Hour/Minute/Second encoding of the given OffsetDatetime.

builder_DmyHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #

Given an OffsetFormat, a SubsecondPrecision, and a DatetimeFormat, construct a Text Builder corresponding to the Day/Month/Year,Hour/Minute/Second-encoding of the given OffsetDatetime.

parser_YmdHMSz :: OffsetFormat -> DatetimeFormat -> Parser OffsetDatetime Source #

Parse a Year/Month/Day,Hour/Minute/Second-encoded OffsetDatetime that was encoded using the given OffsetFormat and DatetimeFormat.

parser_DmyHMSz :: OffsetFormat -> DatetimeFormat -> Parser OffsetDatetime Source #

Parse a Day/Month/Year,Hour/Minute/Second-encoded OffsetDatetime that was encoded using the given OffsetFormat and DatetimeFormat.

builder_DmyIMS_p_z :: OffsetFormat -> MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #

Given an OffsetFormat, a MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct a Text Builder corresponding to the Day/Month/Year,IMS encoding of the given OffsetDatetime.

builderW3Cz :: OffsetDatetime -> Builder Source #

Construct a Text Builder corresponding to the w3c-formatting of the given OffsetDatetime.

UTF-8 ByteString

builderUtf8_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #

Given an OffsetFormat, a SubsecondPrecision, and a DatetimeFormat, construct a ByteString Builder corresponding to the Year/Month/Day,Hour/Minute/Second encoding of the given OffsetDatetime.

parserUtf8_YmdHMSz :: OffsetFormat -> DatetimeFormat -> Parser OffsetDatetime Source #

Parse a Year/Month/Day,Hour/Minute/Second-encoded OffsetDatetime that was encoded using the given OffsetFormat and DatetimeFormat.

builderUtf8_YmdIMS_p_z :: OffsetFormat -> MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #

Given an OffsetFormat, a 'MeridiemLocale, a SubsecondPrecision, and a DatetimeFormat, construct a ByteString Builder corresponding to a Year/Month/Day,IMS-encoded OffsetDatetime.

builderUtf8W3Cz :: OffsetDatetime -> Builder Source #

Construct a ByteString Builder corresponding to the W3C encoding of the given Datetime.

Offset

Text

encodeOffset :: OffsetFormat -> Offset -> Text Source #

Encode an Offset to Text using the given OffsetFormat.

builderOffset :: OffsetFormat -> Offset -> Builder Source #

Construct a Builder corresponding to the given Offset encoded using the given OffsetFormat.

decodeOffset :: OffsetFormat -> Text -> Maybe Offset Source #

Decode an Offset from Text that was encoded using the given OffsetFormat.

parserOffset :: OffsetFormat -> Parser Offset Source #

Parse an Offset that was encoded using the given OffsetFormat.

UTF-8 ByteString

builderOffsetUtf8 :: OffsetFormat -> Offset -> Builder Source #

Construct a ByteString Builder corresponding to the encoding of an Offset using the given OffsetFormat.

decodeOffsetUtf8 :: OffsetFormat -> ByteString -> Maybe Offset Source #

Decode an Offset from a ByteString that was encoded using the given OffsetFormat.

parserOffsetUtf8 :: OffsetFormat -> Parser Offset Source #

Parse an Offset that was encoded using the given OffsetFormat.

Timespan

Text

builderTimespan :: SubsecondPrecision -> Timespan -> Builder Source #

Construct a Text Builder corresponding to an encoding of the given Timespan using the given SubsecondPrecision.

UTF-8 ByteString

encodeTimespanUtf8 :: SubsecondPrecision -> Timespan -> ByteString Source #

Given a SubsecondPrecision, construct a ByteString corresponding to an encoding of the given Timespan.

builderTimespanUtf8 :: SubsecondPrecision -> Timespan -> Builder Source #

Given a SubsecondPrecision, construct a ByteString Builder corresponding to an encoding of the given Timespan.

TimeInterval

within :: Time -> TimeInterval -> Bool Source #

Is the given Time within the TimeInterval?

timeIntervalToTimespan :: TimeInterval -> Timespan Source #

Convert a TimeInterval to a Timespan. This is equivalent to width.

whole :: TimeInterval Source #

The TimeInterval that covers the entire range of Times that Chronos supports.

\(t :: Time) -> within t whole

singleton :: Time -> TimeInterval Source #

The singleton (degenerate) TimeInterval.

lowerBound :: TimeInterval -> Time Source #

Get the lower bound of the TimeInterval.

upperBound :: TimeInterval -> Time Source #

Get the upper bound of the TimeInterval.

width :: TimeInterval -> Timespan Source #

The width of the TimeInterval. This is equivalent to timeIntervalToTimespan.

timeIntervalBuilder :: Time -> Time -> TimeInterval Source #

A smart constructor for TimeInterval. In general, you should prefer using this over the TimeInterval constructor, since it maintains the invariant that lowerBound interval <= upperBound interval.

Types

newtype Day Source #

A day represented as the modified Julian date, the number of days since midnight on November 17, 1858.

Constructors

Day 

Fields

Instances
Enum Day Source # 
Instance details

Defined in Chronos

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day Source # 
Instance details

Defined in Chronos

Methods

(==) :: Day -> Day -> Bool #

(/=) :: Day -> Day -> Bool #

Ord Day Source # 
Instance details

Defined in Chronos

Methods

compare :: Day -> Day -> Ordering #

(<) :: Day -> Day -> Bool #

(<=) :: Day -> Day -> Bool #

(>) :: Day -> Day -> Bool #

(>=) :: Day -> Day -> Bool #

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Read Day Source # 
Instance details

Defined in Chronos

Show Day Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Hashable Day Source # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Day -> Int #

hash :: Day -> Int #

ToJSON Day Source # 
Instance details

Defined in Chronos

FromJSON Day Source # 
Instance details

Defined in Chronos

Storable Day Source # 
Instance details

Defined in Chronos

Methods

sizeOf :: Day -> Int #

alignment :: Day -> Int #

peekElemOff :: Ptr Day -> Int -> IO Day #

pokeElemOff :: Ptr Day -> Int -> Day -> IO () #

peekByteOff :: Ptr b -> Int -> IO Day #

pokeByteOff :: Ptr b -> Int -> Day -> IO () #

peek :: Ptr Day -> IO Day #

poke :: Ptr Day -> Day -> IO () #

Prim Day Source # 
Instance details

Defined in Chronos

Torsor Day Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Day -> Day #

difference :: Day -> Day -> Int #

newtype DayOfWeek Source #

The day of the week.

Constructors

DayOfWeek 

Fields

Instances
Eq DayOfWeek Source # 
Instance details

Defined in Chronos

Ord DayOfWeek Source # 
Instance details

Defined in Chronos

Read DayOfWeek Source # 
Instance details

Defined in Chronos

Show DayOfWeek Source # 
Instance details

Defined in Chronos

Hashable DayOfWeek Source # 
Instance details

Defined in Chronos

newtype DayOfMonth Source #

The day of the month.

Constructors

DayOfMonth 

Fields

Instances
Enum DayOfMonth Source # 
Instance details

Defined in Chronos

Eq DayOfMonth Source # 
Instance details

Defined in Chronos

Ord DayOfMonth Source # 
Instance details

Defined in Chronos

Read DayOfMonth Source # 
Instance details

Defined in Chronos

Show DayOfMonth Source # 
Instance details

Defined in Chronos

Prim DayOfMonth Source # 
Instance details

Defined in Chronos

Unbox DayOfMonth Source # 
Instance details

Defined in Chronos

Vector Vector DayOfMonth Source # 
Instance details

Defined in Chronos

MVector MVector DayOfMonth Source # 
Instance details

Defined in Chronos

newtype Vector DayOfMonth Source # 
Instance details

Defined in Chronos

newtype MVector s DayOfMonth Source # 
Instance details

Defined in Chronos

newtype DayOfYear Source #

The day of the year.

Constructors

DayOfYear 

Fields

Instances
Eq DayOfYear Source # 
Instance details

Defined in Chronos

Ord DayOfYear Source # 
Instance details

Defined in Chronos

Read DayOfYear Source # 
Instance details

Defined in Chronos

Show DayOfYear Source # 
Instance details

Defined in Chronos

Prim DayOfYear Source # 
Instance details

Defined in Chronos

newtype Month Source #

The month of the year.

Constructors

Month 

Fields

Instances
Bounded Month Source #

Month starts at 0 and ends at 11 (January to December)

Instance details

Defined in Chronos

Enum Month Source # 
Instance details

Defined in Chronos

Eq Month Source # 
Instance details

Defined in Chronos

Methods

(==) :: Month -> Month -> Bool #

(/=) :: Month -> Month -> Bool #

Ord Month Source # 
Instance details

Defined in Chronos

Methods

compare :: Month -> Month -> Ordering #

(<) :: Month -> Month -> Bool #

(<=) :: Month -> Month -> Bool #

(>) :: Month -> Month -> Bool #

(>=) :: Month -> Month -> Bool #

max :: Month -> Month -> Month #

min :: Month -> Month -> Month #

Read Month Source # 
Instance details

Defined in Chronos

Show Month Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

Prim Month Source # 
Instance details

Defined in Chronos

Unbox Month Source # 
Instance details

Defined in Chronos

Vector Vector Month Source # 
Instance details

Defined in Chronos

MVector MVector Month Source # 
Instance details

Defined in Chronos

newtype Vector Month Source # 
Instance details

Defined in Chronos

newtype MVector s Month Source # 
Instance details

Defined in Chronos

newtype Year Source #

The number of years elapsed since the beginning of the Common Era.

Constructors

Year 

Fields

Instances
Eq Year Source # 
Instance details

Defined in Chronos

Methods

(==) :: Year -> Year -> Bool #

(/=) :: Year -> Year -> Bool #

Ord Year Source # 
Instance details

Defined in Chronos

Methods

compare :: Year -> Year -> Ordering #

(<) :: Year -> Year -> Bool #

(<=) :: Year -> Year -> Bool #

(>) :: Year -> Year -> Bool #

(>=) :: Year -> Year -> Bool #

max :: Year -> Year -> Year #

min :: Year -> Year -> Year #

Read Year Source # 
Instance details

Defined in Chronos

Show Year Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Year -> ShowS #

show :: Year -> String #

showList :: [Year] -> ShowS #

newtype Offset Source #

Constructors

Offset 

Fields

Instances
Enum Offset Source # 
Instance details

Defined in Chronos

Eq Offset Source # 
Instance details

Defined in Chronos

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Ord Offset Source # 
Instance details

Defined in Chronos

Read Offset Source # 
Instance details

Defined in Chronos

Show Offset Source # 
Instance details

Defined in Chronos

ToJSON Offset Source # 
Instance details

Defined in Chronos

ToJSONKey Offset Source # 
Instance details

Defined in Chronos

FromJSON Offset Source # 
Instance details

Defined in Chronos

FromJSONKey Offset Source # 
Instance details

Defined in Chronos

Torsor Offset Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Offset -> Offset #

difference :: Offset -> Offset -> Int #

newtype Time Source #

POSIX time with nanosecond resolution.

Constructors

Time 

Fields

Instances
Bounded Time Source # 
Instance details

Defined in Chronos

Eq Time Source # 
Instance details

Defined in Chronos

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Ord Time Source # 
Instance details

Defined in Chronos

Methods

compare :: Time -> Time -> Ordering #

(<) :: Time -> Time -> Bool #

(<=) :: Time -> Time -> Bool #

(>) :: Time -> Time -> Bool #

(>=) :: Time -> Time -> Bool #

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

Read Time Source # 
Instance details

Defined in Chronos

Show Time Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Hashable Time Source # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Time -> Int #

hash :: Time -> Int #

ToJSON Time Source # 
Instance details

Defined in Chronos

FromJSON Time Source # 
Instance details

Defined in Chronos

Storable Time Source # 
Instance details

Defined in Chronos

Methods

sizeOf :: Time -> Int #

alignment :: Time -> Int #

peekElemOff :: Ptr Time -> Int -> IO Time #

pokeElemOff :: Ptr Time -> Int -> Time -> IO () #

peekByteOff :: Ptr b -> Int -> IO Time #

pokeByteOff :: Ptr b -> Int -> Time -> IO () #

peek :: Ptr Time -> IO Time #

poke :: Ptr Time -> Time -> IO () #

Prim Time Source # 
Instance details

Defined in Chronos

Torsor Time Timespan Source # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

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.

Constructors

DayOfWeekMatch 

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.

Constructors

MonthMatch 

Fields

newtype UnboxedMonthMatch a Source #

Like MonthMatch, but the matched value can have an instance of Unbox.

newtype Timespan Source #

A timespan. This is represented internally as a number of nanoseconds.

Constructors

Timespan 

Fields

Instances
Eq Timespan Source # 
Instance details

Defined in Chronos

Ord Timespan Source # 
Instance details

Defined in Chronos

Read Timespan Source # 
Instance details

Defined in Chronos

Show Timespan Source # 
Instance details

Defined in Chronos

Semigroup Timespan Source # 
Instance details

Defined in Chronos

Monoid Timespan Source # 
Instance details

Defined in Chronos

ToJSON Timespan Source # 
Instance details

Defined in Chronos

FromJSON Timespan Source # 
Instance details

Defined in Chronos

Additive Timespan Source # 
Instance details

Defined in Chronos

Torsor Time Timespan Source # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

Scaling Timespan Int64 Source # 
Instance details

Defined in Chronos

Methods

scale :: Int64 -> Timespan -> Timespan #

data Date Source #

A date as represented by the Gregorian calendar.

Constructors

Date 
Instances
Enum Date Source # 
Instance details

Defined in Chronos

Methods

succ :: Date -> Date #

pred :: Date -> Date #

toEnum :: Int -> Date #

fromEnum :: Date -> Int #

enumFrom :: Date -> [Date] #

enumFromThen :: Date -> Date -> [Date] #

enumFromTo :: Date -> Date -> [Date] #

enumFromThenTo :: Date -> Date -> Date -> [Date] #

Eq Date Source # 
Instance details

Defined in Chronos

Methods

(==) :: Date -> Date -> Bool #

(/=) :: Date -> Date -> Bool #

Ord Date Source # 
Instance details

Defined in Chronos

Methods

compare :: Date -> Date -> Ordering #

(<) :: Date -> Date -> Bool #

(<=) :: Date -> Date -> Bool #

(>) :: Date -> Date -> Bool #

(>=) :: Date -> Date -> Bool #

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

Read Date Source # 
Instance details

Defined in Chronos

Show Date Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

Torsor Date Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Date -> Date #

difference :: Date -> Date -> Int #

data OrdinalDate Source #

An OrdinalDate is a Year and the number of days elapsed since the Year began.

Instances
Enum OrdinalDate Source # 
Instance details

Defined in Chronos

Eq OrdinalDate Source # 
Instance details

Defined in Chronos

Ord OrdinalDate Source # 
Instance details

Defined in Chronos

Read OrdinalDate Source # 
Instance details

Defined in Chronos

Show OrdinalDate Source # 
Instance details

Defined in Chronos

Torsor OrdinalDate Int Source # 
Instance details

Defined in Chronos

data MonthDate Source #

A month and the day of the month. This does not actually represent a specific date, since this recurs every year.

Constructors

MonthDate 

data Datetime Source #

A Date as represented by the Gregorian calendar and a TimeOfDay.

Constructors

Datetime 
Instances
Eq Datetime Source # 
Instance details

Defined in Chronos

Ord Datetime Source # 
Instance details

Defined in Chronos

Read Datetime Source # 
Instance details

Defined in Chronos

Show Datetime Source # 
Instance details

Defined in Chronos

ToJSON Datetime Source # 
Instance details

Defined in Chronos

data TimeOfDay Source #

A time of day with nanosecond resolution.

data DatetimeFormat Source #

The format of a Datetime. In particular this provides separators for parts of the Datetime and nothing else.

Constructors

DatetimeFormat 

Fields

data OffsetFormat Source #

Formatting settings for a timezone offset.

Constructors

OffsetFormatColonOff

%z (e.g., -0400)

OffsetFormatColonOn

%:z (e.g., -04:00)

OffsetFormatSecondsPrecision

%::z (e.g., -04:00:00)

OffsetFormatColonAuto

%:::z (e.g., -04, +05:30)

Instances
Bounded OffsetFormat Source # 
Instance details

Defined in Chronos

Enum OffsetFormat Source # 
Instance details

Defined in Chronos

Eq OffsetFormat Source # 
Instance details

Defined in Chronos

Ord OffsetFormat Source # 
Instance details

Defined in Chronos

Read OffsetFormat Source # 
Instance details

Defined in Chronos

Show OffsetFormat Source # 
Instance details

Defined in Chronos

Generic OffsetFormat Source # 
Instance details

Defined in Chronos

Associated Types

type Rep OffsetFormat :: Type -> Type #

type Rep OffsetFormat Source # 
Instance details

Defined in Chronos

type Rep OffsetFormat = D1 (MetaData "OffsetFormat" "Chronos" "chronos-1.0.7-FNJ1weYR8Mo8KZhnT2UtCd" False) ((C1 (MetaCons "OffsetFormatColonOff" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OffsetFormatColonOn" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OffsetFormatSecondsPrecision" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OffsetFormatColonAuto" PrefixI False) (U1 :: Type -> Type)))

data DatetimeLocale a Source #

Locale-specific formatting for weekdays and months. The type variable will likely be instantiated to Text or ByteString.

Constructors

DatetimeLocale 

Fields

data MeridiemLocale a Source #

Locale-specific formatting for AM and PM.

Constructors

MeridiemLocale 

Fields

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 lowerBound interval <= upperBound interval (all functions that act on TimeIntervals assume this invariant).

Constructors

TimeInterval !Time !Time