Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- now :: IO Time
- today :: IO Day
- tomorrow :: IO Day
- yesterday :: IO Day
- epoch :: Time
- stopwatch :: IO a -> IO (Timespan, a)
- stopwatch_ :: IO a -> IO Timespan
- stopwatchWith :: Clock -> IO a -> IO (Timespan, a)
- stopwatchWith_ :: Clock -> 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
- 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
- caseMonth :: MonthMatch a -> Month -> a
- w3c :: DatetimeFormat
- slash :: DatetimeFormat
- hyphen :: DatetimeFormat
- compact :: DatetimeFormat
- 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_Mdy :: Maybe Char -> Parser Date
- parser_Dmy :: Maybe Char -> 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
- 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_YmdHMS :: DatetimeFormat -> Parser Datetime
- parser_YmdHMS_opt_S :: DatetimeFormat -> Parser Datetime
- parser_DmyHMS_opt_S :: DatetimeFormat -> Parser Datetime
- decode_DmyHMS :: DatetimeFormat -> Text -> Maybe Datetime
- decode_YmdHMS :: DatetimeFormat -> Text -> Maybe Datetime
- decode_YmdHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime
- decode_DmyHMS_opt_S :: DatetimeFormat -> 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
- 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
- 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
- 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
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.
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 :: Int -> Int -> Int -> Int -> Int -> Int -> Datetime Source #
Construct a Datetime
from year, month, day, hour, minute, second:
>>>
datetimeFromYmdhms 2014 2 26 17 58 52
foobar
Conversion
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 #
ordinalDateToDay :: OrdinalDate -> Day Source #
Build Timespan
Matching
buildDayOfWeekMatch :: a -> a -> a -> a -> a -> a -> a -> DayOfWeekMatch a Source #
buildMonthMatch :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> MonthMatch a Source #
caseMonth :: MonthMatch a -> Month -> a Source #
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 #
Months
Days of Week
Utility
isLeapYear :: Year -> Bool Source #
Textual Conversion
Date
Text
builder_Ymd :: Maybe Char -> Date -> Builder Source #
This could be written much more efficiently since we know the
exact size the resulting Text
will be.
builder_HMS :: SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #
UTF-8 ByteString
Time of Day
Text
builder_IMS_p :: MeridiemLocale Text -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #
builder_IMSp :: MeridiemLocale Text -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #
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 #
builderUtf8_IMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #
builderUtf8_IMSp :: MeridiemLocale ByteString -> SubsecondPrecision -> Maybe Char -> TimeOfDay -> Builder Source #
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.
Datetime
Text
builder_DmyHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builder_DmyIMSp :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builder_DmyIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builder_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
This could be written much more efficiently since we know the
exact size the resulting Text
will be.
builder_YmdIMSp :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builder_YmdIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builderW3C :: Datetime -> Builder Source #
encode_DmyHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #
encode_DmyIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #
encode_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #
encode_YmdIMS_p :: MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Text Source #
decode_DmyHMS :: DatetimeFormat -> Text -> Maybe Datetime Source #
decode_YmdHMS :: DatetimeFormat -> Text -> Maybe Datetime Source #
decode_YmdHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime Source #
decode_DmyHMS_opt_S :: DatetimeFormat -> Text -> Maybe Datetime Source #
UTF-8 ByteString
encodeUtf8_YmdIMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> ByteString Source #
builderUtf8_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builderUtf8_YmdIMSp :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builderUtf8_YmdIMS_p :: MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #
builderUtf8W3C :: Datetime -> Builder Source #
Offset Datetime
Text
encode_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Text Source #
encode_DmyHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Text Source #
builder_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #
builder_DmyHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #
builder_YmdIMS_p_z :: OffsetFormat -> MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #
builder_DmyIMS_p_z :: OffsetFormat -> MeridiemLocale Text -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #
builderW3Cz :: OffsetDatetime -> Builder Source #
UTF-8 ByteString
builderUtf8_YmdHMSz :: OffsetFormat -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #
builderUtf8_YmdIMS_p_z :: OffsetFormat -> MeridiemLocale ByteString -> SubsecondPrecision -> DatetimeFormat -> OffsetDatetime -> Builder Source #
Offset
Text
encodeOffset :: OffsetFormat -> Offset -> Text Source #
builderOffset :: OffsetFormat -> Offset -> Builder Source #
decodeOffset :: OffsetFormat -> Text -> Maybe Offset Source #
parserOffset :: OffsetFormat -> Parser Offset Source #
UTF-8 ByteString
encodeOffsetUtf8 :: OffsetFormat -> Offset -> ByteString Source #
builderOffsetUtf8 :: OffsetFormat -> Offset -> Builder Source #
decodeOffsetUtf8 :: OffsetFormat -> ByteString -> Maybe Offset Source #
Timespan
Text
encodeTimespan :: SubsecondPrecision -> Timespan -> Text Source #
builderTimespan :: SubsecondPrecision -> Timespan -> Builder Source #
UTF-8 ByteString
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 # | |
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 # | |
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.
POSIX time with nanosecond resolution.
Instances
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 | |
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 #
newtype MonthMatch a Source #
newtype UnboxedMonthMatch a Source #
A timespan. This is represented internally as a number of nanoseconds.
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 |
A date as represented by the Gregorian calendar.
data OrdinalDate Source #
The year and number of days elapsed since the beginning it 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 time of day.
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 # |
A time of day with nanosecond resolution.
TimeOfDay | |
|
data DatetimeFormat Source #
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 # |
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 | |
|
data MeridiemLocale a Source #
Locale-specific formatting for AM and PM.
MeridiemLocale | |
|