Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
andByteString
. Additionally, Chronos provides functions for encoding time toText
orByteString
. The 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
- now :: IO Time
- today :: IO Day
- tomorrow :: IO Day
- yesterday :: IO Day
- todayDayOfWeek :: IO DayOfWeek
- yesterdayDayOfWeek :: IO DayOfWeek
- tomorrowDayOfWeek :: IO DayOfWeek
- timeToDayOfWeek :: Time -> DayOfWeek
- epoch :: Time
- stopwatch :: IO a -> IO (Timespan, a)
- stopwatch_ :: IO a -> IO Timespan
- datetimeFromYmdhms :: Int -> Int -> Int -> Int -> Int -> Int -> Datetime
- timeFromYmdhms :: Int -> Int -> Int -> Int -> Int -> Int -> Time
- timeToDatetime :: Time -> Datetime
- datetimeToTime :: Datetime -> Time
- datetimeToDayOfWeek :: Datetime -> DayOfWeek
- dateToDayOfWeek :: Date -> DayOfWeek
- timeToOffsetDatetime :: Offset -> Time -> OffsetDatetime
- offsetDatetimeToTime :: OffsetDatetime -> Time
- timeToDayTruncate :: Time -> Day
- dayToTimeMidnight :: Day -> Time
- dayToDate :: Day -> Date
- dateToDay :: Date -> Day
- dayToOrdinalDate :: Day -> OrdinalDate
- ordinalDateToDay :: OrdinalDate -> Day
- monthDateToDayOfYear :: Bool -> MonthDate -> DayOfYear
- dayOfYearToMonthDay :: Bool -> DayOfYear -> MonthDate
- second :: Timespan
- minute :: Timespan
- hour :: Timespan
- day :: Timespan
- week :: Timespan
- buildDayOfWeekMatch :: a -> a -> a -> a -> a -> a -> a -> DayOfWeekMatch a
- buildMonthMatch :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> MonthMatch a
- buildUnboxedMonthMatch :: Unbox a => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> UnboxedMonthMatch a
- caseDayOfWeek :: DayOfWeekMatch a -> DayOfWeek -> a
- caseMonth :: MonthMatch a -> Month -> a
- caseUnboxedMonth :: Unbox a => UnboxedMonthMatch a -> Month -> a
- w3c :: DatetimeFormat
- slash :: DatetimeFormat
- hyphen :: DatetimeFormat
- compact :: DatetimeFormat
- timeParts :: Offset -> Time -> TimeParts
- january :: Month
- february :: Month
- march :: Month
- april :: Month
- may :: Month
- june :: Month
- july :: Month
- august :: Month
- september :: Month
- october :: Month
- november :: Month
- december :: Month
- sunday :: DayOfWeek
- monday :: DayOfWeek
- tuesday :: DayOfWeek
- wednesday :: DayOfWeek
- thursday :: DayOfWeek
- friday :: DayOfWeek
- saturday :: DayOfWeek
- daysInMonth :: Bool -> Month -> Int
- isLeapYear :: Year -> Bool
- observedOffsets :: Vector Offset
- builder_Ymd :: Maybe Char -> Date -> Builder
- builder_Dmy :: Maybe Char -> Date -> Builder
- builder_HMS :: SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder
- parser_Ymd :: Maybe Char -> Parser Date
- parser_Ymd_lenient :: Parser Date
- parser_Mdy :: Maybe Char -> Parser Date
- parser_Mdy_lenient :: Parser Date
- parser_Dmy :: Maybe Char -> Parser Date
- parser_Dmy_lenient :: Parser Date
- builderUtf8_Ymd :: Maybe Char -> Date -> Builder
- parserUtf8_Ymd :: Maybe Char -> Parser Date
- builder_IMS_p :: MeridiemLocale Text -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder
- builder_IMSp :: MeridiemLocale Text -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder
- parser_HMS :: Maybe Char -> Parser TimeOfDay
- parser_HMS_opt_S :: Maybe Char -> Parser TimeOfDay
- builderUtf8_HMS :: SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder
- builderUtf8_IMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder
- builderUtf8_IMSp :: MeridiemLocale ByteString -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder
- parserUtf8_HMS :: Maybe Char -> Parser TimeOfDay
- parserUtf8_HMS_opt_S :: Maybe Char -> Parser TimeOfDay
- zeptoUtf8_HMS :: Maybe Char -> Parser TimeOfDay
- builder_DmyHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builder_DmyIMSp :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builder_DmyIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builder_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builder_YmdIMSp :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builder_YmdIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builderW3C :: Datetime -> Builder
- builderIso8601 :: Datetime -> Builder
- encodeIso8601 :: Datetime -> Text
- encode_Ymd :: Maybe Char -> Date -> Text
- encode_Dmy :: Maybe Char -> Date -> Text
- encode_DmyHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Text
- encode_DmyIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Text
- encode_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Text
- encode_YmdIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Text
- parser_DmyHMS :: DatetimeFormat -> Parser Datetime
- parser_DmyHMS_lenient :: Parser Datetime
- parser_YmdHMS :: DatetimeFormat -> Parser Datetime
- parser_YmdHMS_lenient :: Parser Datetime
- parser_YmdHMS_opt_S :: DatetimeFormat -> Parser Datetime
- parser_YmdHMS_opt_S_lenient :: Parser Datetime
- parser_DmyHMS_opt_S :: DatetimeFormat -> Parser Datetime
- parser_DmyHMS_opt_S_lenient :: Parser Datetime
- parser_MdyHMS :: DatetimeFormat -> Parser Datetime
- parser_MdyHMS_lenient :: Parser Datetime
- parser_MdyHMS_opt_S :: DatetimeFormat -> Parser Datetime
- parser_MdyHMS_opt_S_lenient :: Parser Datetime
- parser_lenient :: Parser Datetime
- decode_DmyHMS :: DatetimeFormat -> Text -> Maybe Datetime
- decode_DmyHMS_lenient :: Text -> Maybe Datetime
- decode_MdyHMS :: DatetimeFormat -> Text -> Maybe Datetime
- decode_MdyHMS_lenient :: Text -> Maybe Datetime
- decode_MdyHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime
- decode_MdyHMS_opt_S_lenient :: Text -> Maybe Datetime
- decode_YmdHMS :: DatetimeFormat -> Text -> Maybe Datetime
- decode_YmdHMS_lenient :: Text -> Maybe Datetime
- decode_YmdHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime
- decode_YmdHMS_opt_S_lenient :: Text -> Maybe Datetime
- decode_DmyHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime
- decode_DmyHMS_opt_S_lenient :: Text -> Maybe Datetime
- decode_lenient :: Text -> Maybe Datetime
- encodeUtf8_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> ByteString
- encodeUtf8_YmdIMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> ByteString
- builderUtf8_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builderUtf8_YmdIMSp :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builderUtf8_YmdIMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder
- builderUtf8W3C :: Datetime -> Builder
- decodeUtf8_YmdHMS :: DatetimeFormat -> ByteString -> Maybe Datetime
- decodeUtf8_YmdHMS_opt_S :: DatetimeFormat -> ByteString -> Maybe Datetime
- parserUtf8_YmdHMS :: DatetimeFormat -> Parser Datetime
- parserUtf8_YmdHMS_opt_S :: DatetimeFormat -> Parser Datetime
- zeptoUtf8_YmdHMS :: DatetimeFormat -> Parser Datetime
- boundedBuilderUtf8BytesIso8601Zoneless :: Datetime -> Builder 44
- decodeUtf8BytesIso8601Zoneless :: Bytes -> Maybe Datetime
- decodeShortTextIso8601Zoneless :: ShortText -> Maybe Datetime
- encodeShortTextIso8601Zulu :: Datetime -> ShortText
- encodeShortTextIso8601Zoneless :: Datetime -> ShortText
- encode_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Text
- encode_DmyHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Text
- builder_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder
- builder_DmyHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder
- parser_YmdHMSz :: OffsetFormat -> DatetimeFormat -> Parser OffsetDatetime
- parser_DmyHMSz :: OffsetFormat -> DatetimeFormat -> Parser OffsetDatetime
- builder_YmdIMS_p_z :: OffsetFormat -> MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder
- builder_DmyIMS_p_z :: OffsetFormat -> MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder
- builderW3Cz :: OffsetDatetime -> Builder
- builderUtf8_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder
- parserUtf8_YmdHMSz :: OffsetFormat -> DatetimeFormat -> Parser OffsetDatetime
- builderUtf8_YmdIMS_p_z :: OffsetFormat -> MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder
- builderUtf8W3Cz :: OffsetDatetime -> Builder
- parserUtf8BytesIso8601 :: Parser () s OffsetDatetime
- boundedBuilderUtf8BytesIso8601 :: OffsetDatetime -> Builder 50
- decodeUtf8BytesIso8601 :: Bytes -> Maybe OffsetDatetime
- decodeShortTextIso8601 :: ShortText -> Maybe OffsetDatetime
- encodeShortTextIso8601 :: OffsetDatetime -> ShortText
- encodeOffset :: OffsetFormat -> Offset -> Text
- builderOffset :: OffsetFormat -> Offset -> Builder
- decodeOffset :: OffsetFormat -> Text -> Maybe Offset
- parserOffset :: OffsetFormat -> Parser Offset
- encodeOffsetUtf8 :: OffsetFormat -> Offset -> ByteString
- builderOffsetUtf8 :: OffsetFormat -> Offset -> Builder
- decodeOffsetUtf8 :: OffsetFormat -> ByteString -> Maybe Offset
- parserOffsetUtf8 :: OffsetFormat -> Parser Offset
- encodeTimespan :: SubsecondPrecision -> Timespan -> Text
- builderTimespan :: SubsecondPrecision -> Timespan -> Builder
- encodeTimespanUtf8 :: SubsecondPrecision -> Timespan -> ByteString
- builderTimespanUtf8 :: SubsecondPrecision -> Timespan -> Builder
- within :: Time -> TimeInterval -> Bool
- timeIntervalToTimespan :: TimeInterval -> Timespan
- whole :: TimeInterval
- singleton :: Time -> TimeInterval
- lowerBound :: TimeInterval -> Time
- upperBound :: TimeInterval -> Time
- width :: TimeInterval -> Timespan
- timeIntervalBuilder :: Time -> Time -> TimeInterval
- (...) :: Time -> Time -> TimeInterval
- 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
- _timeToDatetime :: forall f. Functor f => (Datetime -> f Datetime) -> Time -> f Time
- _datetimeToTime :: forall f. Functor f => (Time -> f Time) -> Datetime -> f Datetime
- _dayToDate :: forall f. Functor f => (Date -> f Date) -> Day -> f Day
- _dateToDay :: forall f. Functor f => (Day -> f Day) -> Date -> f Date
- _getDay :: Functor f => (Int -> f Int) -> Day -> f Day
- _getDayOfWeek :: Functor f => (Int -> f Int) -> DayOfWeek -> f DayOfWeek
- _getDayOfMonth :: Functor f => (Int -> f Int) -> DayOfMonth -> f DayOfMonth
- _getDayOfYear :: Functor f => (Int -> f Int) -> DayOfYear -> f DayOfYear
- _getMonth :: Functor f => (Int -> f Int) -> Month -> f Month
- _getOffset :: Functor f => (Int -> f Int) -> Offset -> f Offset
- _getTime :: Functor f => (Int64 -> f Int64) -> Time -> f Time
- _getTimespan :: Functor f => (Int64 -> f Int64) -> Timespan -> f Timespan
- _dateYear :: Functor f => (Year -> f Year) -> Date -> f Date
- _dateMonth :: Functor f => (Month -> f Month) -> Date -> f Date
- _dateDay :: Functor f => (DayOfMonth -> f DayOfMonth) -> Date -> f Date
- _ordinalDateYear :: Functor f => (Year -> f Year) -> OrdinalDate -> f OrdinalDate
- _ordinalDateDayOfYear :: Functor f => (DayOfYear -> f DayOfYear) -> OrdinalDate -> f OrdinalDate
- _monthDateMonth :: Functor f => (Month -> f Month) -> MonthDate -> f MonthDate
- _monthDateDay :: Functor f => (DayOfMonth -> f DayOfMonth) -> MonthDate -> f MonthDate
- _datetimeDate :: Functor f => (Date -> f Date) -> Datetime -> f Datetime
- _datetimeTime :: Functor f => (TimeOfDay -> f TimeOfDay) -> Datetime -> f Datetime
- _offsetDatetimeDatetime :: Functor f => (Datetime -> f Datetime) -> OffsetDatetime -> f OffsetDatetime
- _offsetDatetimeOffset :: Functor f => (Offset -> f Offset) -> OffsetDatetime -> f OffsetDatetime
- _timeOfDayHour :: Functor f => (Int -> f Int) -> TimeOfDay -> f TimeOfDay
- _timeOfDayMinute :: Functor f => (Int -> f Int) -> TimeOfDay -> f TimeOfDay
- _timeOfDayNanoseconds :: Functor f => (Int64 -> f Int64) -> TimeOfDay -> f TimeOfDay
Functions
Current
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.
Construction
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}}
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 #
datetimeToTime :: Datetime -> Time Source #
timeToOffsetDatetime :: Offset -> Time -> OffsetDatetime Source #
Convert Time
to OffsetDatetime
by providing an Offset
.
offsetDatetimeToTime :: OffsetDatetime -> Time Source #
Convert OffsetDatetime
to Time
.
timeToDayTruncate :: Time -> Day Source #
Convert Time
to Day
. This function is lossy; consequently, it
does not roundtrip with dayToTimeMidnight
.
dayToOrdinalDate :: Day -> OrdinalDate Source #
Convert a Day
to an OrdinalDate
.
ordinalDateToDay :: OrdinalDate -> Day Source #
Convert an OrdinalDate
to a Day
.
Build Timespan
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.
caseDayOfWeek :: DayOfWeekMatch a -> DayOfWeek -> a Source #
Match a DayOfWeek
against a DayOfWeekMatch
.
caseMonth :: MonthMatch a -> Month -> a Source #
Match a Month
against a MonthMatch
.
caseUnboxedMonth :: Unbox a => UnboxedMonthMatch a -> Month -> a Source #
Match a Month
against an UnboxedMonthMatch
.
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
Days of Week
Utility
Return the number of days in a given month.
isLeapYear :: Year -> Bool Source #
observedOffsets :: Vector Offset Source #
All UTC time offsets. See List of UTC time offsets.
Textual Conversion
Date
Text
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_Ymd_lenient :: Parser Date Source #
Parse a Year/Month/Day-encoded Date
that either has no separators or
uses any non-numeric character for each separator.
parser_Mdy :: Maybe Char -> Parser Date Source #
Parse a Month/Day/Year-encoded Date
that uses the
given separator.
parser_Mdy_lenient :: Parser Date Source #
Parse a Month/Day/Year-encoded Date
that either has no separators or
uses any non-numeric character for each separator.
parser_Dmy :: Maybe Char -> Parser Date Source #
Parse a Day/Month/Year-encoded Date
that uses the
given separator.
parser_Dmy_lenient :: Parser Date Source #
Parse a Day/Month/Year-encoded Date
that either has no separators or
uses any non-numeric character for each 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/Minute/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
.
Deprecated. This is just a poorly named alias for builderIso8601
.
builderIso8601 :: Datetime -> Builder Source #
encodeIso8601 :: Datetime -> Text Source #
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_lenient :: Parser Datetime Source #
Parses a Year/Month/Day,Hour/Minute/Second-encoded Datetime
that was
encoded with either no separators or any non-numeric character for each
separator.
parser_YmdHMS_opt_S :: DatetimeFormat -> Parser Datetime Source #
Parses a Year/Month/Date,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with the given DatetimeFormat
and with either of
the following time formats:
%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_YmdHMS_opt_S_lenient :: Parser Datetime Source #
Parses a Year/Month/Date,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with either no separators or any non-numeric
character for each separator and with either of the following time formats:
%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.
parser_DmyHMS_opt_S_lenient :: Parser Datetime Source #
Parse a Day/Month/Year,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with either no separators or any non-numeric
character for each separator and with either of the following time formats:
%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_MdyHMS :: DatetimeFormat -> Parser Datetime Source #
Parses a Month/Day/Year,Hour/Minute/Second-encoded Datetime
that was encoded using the given DatetimeFormat
.
parser_MdyHMS_lenient :: Parser Datetime Source #
Parses a Month/Day/Year,Hour/Minute/Second-encoded Datetime
that was
encoded with either no separators or any non-numeric character for each
separator.
parser_MdyHMS_opt_S :: DatetimeFormat -> Parser Datetime Source #
Parse a Month/Day/Year,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with with the given DatetimeFormat
and with
either of the following time formats:
%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.
parser_MdyHMS_opt_S_lenient :: Parser Datetime Source #
Parse a Month/Day/Year,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with either no separators or any non-numeric
character for each separator and with either of the following time formats:
%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.
parser_lenient :: Parser Datetime Source #
Parses a Datetime
from Text
that was encoded with any of the following
formats and with either no separators or any non-numeric character for each
separator.
%Y-%M-%D %H:%M
%Y-%M-%D %H:%M:%S
%D-%M-%Y %H:%M
%D-%M-%Y %H:%M:%S
%M-%D-%Y %H:%M
%M-%D-%Y %H:%M:%S
That is, the seconds and subseconds part is optional. If it is not provided, it is assumed to be zero. Note that this is the least performant parser due to backtracking
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_MdyHMS :: DatetimeFormat -> Text -> Maybe Datetime Source #
Decode a Month/Day/Year,Hour/Minute/Second-encoded Datetime
from Text
that was encoded with the given DatetimeFormat
.
decode_MdyHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime Source #
Decode a Month/Day/Year,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with the given DatetimeFormat
and with either of
the following time formats:
%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.
decode_MdyHMS_opt_S_lenient :: Text -> Maybe Datetime Source #
Parse a Month/Day/Year,Hour/Minute/Second-encoded Datetime
from
Text
with either no separators or any non-numeric character for each
separator and with either of the following time formats:
%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.
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 #
Decode a Year/Month/Date,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with the given DatetimeFormat
and with either of
the following time formats:
%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_YmdHMS_opt_S_lenient :: Text -> Maybe Datetime Source #
Decode a Year/Month/Date,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with either no separators or any non-numeric
character for each separator and with either of the following time formats:
%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 #
Decode a Day/Month/Year,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with with the given DatetimeFormat
and with
either of the following time formats:
%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_lenient :: Text -> Maybe Datetime Source #
Decode a Day/Month/Year,Hour/Minute/Second-encoded Datetime
from
Text
that was encoded with either no separators or any non-numeric
character for each separator and with either of the following time formats:
%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_lenient :: Text -> Maybe Datetime Source #
Parses text that was encoded in DMY, YMD, or MDY format with optional seconds and any non-numeric character as separators.
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
.
UTF-8 Bytes
boundedBuilderUtf8BytesIso8601Zoneless :: Datetime -> Builder 44 Source #
Encode a datetime with ISO-8601. The result does not include any indication of a time zone. If the subsecond part is zero, it is suppressed. Examples of output:
2021-01-05T23:00:51 2021-01-05T23:00:52.123000000 2021-01-05T23:00:53.674094347
Short Text
decodeShortTextIso8601Zoneless :: ShortText -> Maybe Datetime Source #
Decode an ISO-8601-encode datetime. The encoded time must not by suffixed
by an offset. Any offset (e.g. -05:00
, +00:00
, Z
) will cause a decode
failure.
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_YmdIMS_p_z :: OffsetFormat -> MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #
Given an OffsetFormat
, a MeridiemLocale
, a
SubsecondPrecision
, and DatetimeFormat
, construct a
Text
Builder
corresponding to a Year/Month/Day,IMS-encoding
of the given OffsetDatetime
.
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
.
UTF-8 Bytes
parserUtf8BytesIso8601 :: Parser () s OffsetDatetime Source #
Consume an ISO-8601-encoded datetime with offset. This will consume any of the following:
2021-12-05T23:01:09Z 2021-12-05T23:01:09.000Z 2021-12-05T23:01:09.123456789Z 2021-12-05T23:01:09+05:00 2021-12-05T23:01:09.357-11:00
ShortText
decodeShortTextIso8601 :: ShortText -> Maybe OffsetDatetime Source #
Decode an ISO-8601-encode datetime. The encoded time must include an offset
(e.g. -05:00
, +00:00
, Z
).
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
encodeOffsetUtf8 :: OffsetFormat -> Offset -> ByteString Source #
Encode an Offset
as a ByteString
using the given OffsetFormat
.
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
encodeTimespan :: SubsecondPrecision -> Timespan -> Text Source #
Encode a Timespan
as Text
using the given SubsecondPrecision
.
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 Time
s 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
(...) :: Time -> Time -> TimeInterval infix 3 Source #
An infix timeIntervalBuilder
.
Types
A day represented as the modified Julian date, the number of days since midnight on November 17, 1858.
Instances
Enum Day Source # | |
Eq Day Source # | |
Ord Day Source # | |
Read Day Source # | |
Show Day Source # | |
Hashable Day Source # | |
ToJSON Day Source # | |
FromJSON Day Source # | |
Storable Day Source # | |
NFData 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
Eq DayOfYear Source # | |
Ord DayOfYear Source # | |
Defined in Chronos | |
Read DayOfYear Source # | |
Show DayOfYear Source # | |
NFData DayOfYear Source # | |
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
Enum Offset Source # | |
Defined in Chronos | |
Eq Offset Source # | |
Ord Offset Source # | |
Read Offset Source # | |
Show Offset Source # | |
ToJSON Offset Source # | |
ToJSONKey Offset Source # | |
Defined in Chronos | |
FromJSON Offset Source # | |
FromJSONKey Offset Source # | |
Defined in Chronos | |
NFData Offset Source # | |
Torsor Offset Int Source # | |
POSIX time with nanosecond resolution.
Instances
Bounded Time Source # | |
Eq Time Source # | |
Ord Time Source # | |
Read Time Source # | |
Show Time Source # | |
Hashable Time Source # | |
ToJSON Time Source # | |
FromJSON Time Source # | |
Storable Time Source # | |
Defined in Chronos | |
NFData 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
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 # | |
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 -> () # |
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
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 # | |
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 -> () # |
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
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 # | |
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 -> () # |
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 | |
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 # | |
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 -> () # |
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 | |
|
Lenses
_timeToDatetime :: forall f. Functor f => (Datetime -> f Datetime) -> Time -> f Time Source #
A lens-compatible variant of half of the timeToDatetime
/datetimeToTime
isomorphism.
Note: We do not provide an iso as that requires a dependence on the profunctor
package.
_datetimeToTime :: forall f. Functor f => (Time -> f Time) -> Datetime -> f Datetime Source #
A lens-compatible variant of half of the timeToDatetime
/datetimeToTime
isomorphism.
Note: We do not provide an iso as that requires a dependence on the profunctor
package.
_getDay :: Functor f => (Int -> f Int) -> Day -> f Day Source #
a lens for accessing the getDay
field.
_getDayOfWeek :: Functor f => (Int -> f Int) -> DayOfWeek -> f DayOfWeek Source #
a lens for accessing the getDayOfWeek
field.
_getDayOfMonth :: Functor f => (Int -> f Int) -> DayOfMonth -> f DayOfMonth Source #
a lens for accessing the getDayOfMonth
field.
_getDayOfYear :: Functor f => (Int -> f Int) -> DayOfYear -> f DayOfYear Source #
a lens for accessing the getDayOfYear
field.
_getMonth :: Functor f => (Int -> f Int) -> Month -> f Month Source #
a lens for accessing the getMonth
field.
_getOffset :: Functor f => (Int -> f Int) -> Offset -> f Offset Source #
a lens for accessing the getOffset
field.
_getTime :: Functor f => (Int64 -> f Int64) -> Time -> f Time Source #
a lens for accessing the getTime
field.
_getTimespan :: Functor f => (Int64 -> f Int64) -> Timespan -> f Timespan Source #
a lens for accessing the getTimespan
field.
_dateYear :: Functor f => (Year -> f Year) -> Date -> f Date Source #
a lens for accessing the dateYear
field.
_dateMonth :: Functor f => (Month -> f Month) -> Date -> f Date Source #
a lens for accessing the dateMonth
field.
_dateDay :: Functor f => (DayOfMonth -> f DayOfMonth) -> Date -> f Date Source #
a lens for accessing the dateDay
field.
_ordinalDateYear :: Functor f => (Year -> f Year) -> OrdinalDate -> f OrdinalDate Source #
a lens for accessing the ordinalDateYear
field.
_ordinalDateDayOfYear :: Functor f => (DayOfYear -> f DayOfYear) -> OrdinalDate -> f OrdinalDate Source #
a lens for accessing the ordinalDateDayOfYear
field.
_monthDateMonth :: Functor f => (Month -> f Month) -> MonthDate -> f MonthDate Source #
a lens for accessing the monthDateMonth
field.
_monthDateDay :: Functor f => (DayOfMonth -> f DayOfMonth) -> MonthDate -> f MonthDate Source #
a lens for accessing the monthDateDay
field.
_datetimeDate :: Functor f => (Date -> f Date) -> Datetime -> f Datetime Source #
a lens for accessing the datetimeDate
field.
_datetimeTime :: Functor f => (TimeOfDay -> f TimeOfDay) -> Datetime -> f Datetime Source #
a lens for accessing the datetimeTime
field.
_offsetDatetimeDatetime :: Functor f => (Datetime -> f Datetime) -> OffsetDatetime -> f OffsetDatetime Source #
a lens for accessing the offsetDatetimeDatetime
field.
_offsetDatetimeOffset :: Functor f => (Offset -> f Offset) -> OffsetDatetime -> f OffsetDatetime Source #
a lens for accessing the offsetDatetimeOffset
field.
_timeOfDayHour :: Functor f => (Int -> f Int) -> TimeOfDay -> f TimeOfDay Source #
a lens for accessing the timeOfDayHour
field.
_timeOfDayMinute :: Functor f => (Int -> f Int) -> TimeOfDay -> f TimeOfDay Source #
a lens for accessing the timeOfDayMinute
field.
_timeOfDayNanoseconds :: Functor f => (Int64 -> f Int64) -> TimeOfDay -> f TimeOfDay Source #
a lens for accessing the timeOfDayNanoseconds
field.