chronos-1.0.7: A performant time library

Safe HaskellNone
LanguageHaskell2010

Chronos.Types

Description

Data types for representing different date and time-related information.

Internally, the types Int and Int64 are used to represent everything. These are used even when negative values are not appropriate and even if a smaller fixed-size integer could hold the information. The only cases when Int64 is used are when it is neccessary to represent values with numbers 2^29 or higher. These are typically fields that represent nanoseconds.

Unlike the types in the venerable time library, the types here do not allow the user to work with all dates. Since this library uses fixed-precision integral values instead of Integer, all of the usual problems with overflow should be considered. Notably, PosixTime and TaiTime can only be used to represent time between the years 1680 and 2260. All other types in this library correctly represent time a million years before or after 1970.

The vector unbox instances store data in a reasonably compact manner. For example, the instance for Day has three unboxed vectors: Int for the year, Int8 for the month, and Int8 for the day. This only causes corruption of data if the user is trying to use out-of-bounds values for the month and the day. Users are advised to not use the data types provided here to model non-existent times.

Synopsis

Documentation

newtype Day #

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

Constructors

Day 

Fields

Instances
Enum Day # 
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 # 
Instance details

Defined in Chronos

Methods

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

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

Ord Day # 
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 # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Day #

readList :: ReadS [Day] #

readPrec :: ReadPrec Day #

readListPrec :: ReadPrec [Day] #

Show Day # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Day -> ShowS

show :: Day -> String

showList :: [Day] -> ShowS

Hashable Day # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Day -> Int #

hash :: Day -> Int #

ToJSON Day # 
Instance details

Defined in Chronos

FromJSON Day # 
Instance details

Defined in Chronos

Storable Day # 
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 # 
Instance details

Defined in Chronos

Methods

sizeOf# :: Day -> Int# #

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 # 
Instance details

Defined in Chronos

Methods

add :: Int -> Day -> Day #

difference :: Day -> Day -> Int #

newtype DayOfWeek #

The day of the week.

Constructors

DayOfWeek 

Fields

Instances
Eq DayOfWeek # 
Instance details

Defined in Chronos

Methods

(==) :: DayOfWeek -> DayOfWeek -> Bool

(/=) :: DayOfWeek -> DayOfWeek -> Bool

Ord DayOfWeek # 
Instance details

Defined in Chronos

Methods

compare :: DayOfWeek -> DayOfWeek -> Ordering

(<) :: DayOfWeek -> DayOfWeek -> Bool

(<=) :: DayOfWeek -> DayOfWeek -> Bool

(>) :: DayOfWeek -> DayOfWeek -> Bool

(>=) :: DayOfWeek -> DayOfWeek -> Bool

max :: DayOfWeek -> DayOfWeek -> DayOfWeek

min :: DayOfWeek -> DayOfWeek -> DayOfWeek

Read DayOfWeek # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS DayOfWeek #

readList :: ReadS [DayOfWeek] #

readPrec :: ReadPrec DayOfWeek #

readListPrec :: ReadPrec [DayOfWeek] #

Show DayOfWeek # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> DayOfWeek -> ShowS

show :: DayOfWeek -> String

showList :: [DayOfWeek] -> ShowS

Hashable DayOfWeek # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> DayOfWeek -> Int #

hash :: DayOfWeek -> Int #

newtype DayOfMonth #

The day of the month.

Constructors

DayOfMonth 

Fields

Instances
Enum DayOfMonth # 
Instance details

Defined in Chronos

Eq DayOfMonth # 
Instance details

Defined in Chronos

Methods

(==) :: DayOfMonth -> DayOfMonth -> Bool

(/=) :: DayOfMonth -> DayOfMonth -> Bool

Ord DayOfMonth # 
Instance details

Defined in Chronos

Read DayOfMonth # 
Instance details

Defined in Chronos

Show DayOfMonth # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> DayOfMonth -> ShowS

show :: DayOfMonth -> String

showList :: [DayOfMonth] -> ShowS

Prim DayOfMonth # 
Instance details

Defined in Chronos

Methods

sizeOf# :: DayOfMonth -> Int# #

alignment# :: DayOfMonth -> Int# #

indexByteArray# :: ByteArray# -> Int# -> DayOfMonth #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DayOfMonth#) #

writeByteArray# :: MutableByteArray# s -> Int# -> DayOfMonth -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> DayOfMonth -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> DayOfMonth #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, DayOfMonth#) #

writeOffAddr# :: Addr# -> Int# -> DayOfMonth -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> DayOfMonth -> State# s -> State# s #

Unbox DayOfMonth # 
Instance details

Defined in Chronos

Vector Vector DayOfMonth # 
Instance details

Defined in Chronos

MVector MVector DayOfMonth # 
Instance details

Defined in Chronos

newtype Vector DayOfMonth # 
Instance details

Defined in Chronos

newtype MVector s DayOfMonth # 
Instance details

Defined in Chronos

newtype DayOfYear #

The day of the year.

Constructors

DayOfYear 

Fields

Instances
Eq DayOfYear # 
Instance details

Defined in Chronos

Methods

(==) :: DayOfYear -> DayOfYear -> Bool

(/=) :: DayOfYear -> DayOfYear -> Bool

Ord DayOfYear # 
Instance details

Defined in Chronos

Methods

compare :: DayOfYear -> DayOfYear -> Ordering

(<) :: DayOfYear -> DayOfYear -> Bool

(<=) :: DayOfYear -> DayOfYear -> Bool

(>) :: DayOfYear -> DayOfYear -> Bool

(>=) :: DayOfYear -> DayOfYear -> Bool

max :: DayOfYear -> DayOfYear -> DayOfYear

min :: DayOfYear -> DayOfYear -> DayOfYear

Read DayOfYear # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS DayOfYear #

readList :: ReadS [DayOfYear] #

readPrec :: ReadPrec DayOfYear #

readListPrec :: ReadPrec [DayOfYear] #

Show DayOfYear # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> DayOfYear -> ShowS

show :: DayOfYear -> String

showList :: [DayOfYear] -> ShowS

Prim DayOfYear # 
Instance details

Defined in Chronos

Methods

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 #

newtype Month #

The month of the year.

Constructors

Month 

Fields

Instances
Bounded Month #

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

Instance details

Defined in Chronos

Enum Month # 
Instance details

Defined in Chronos

Eq Month # 
Instance details

Defined in Chronos

Methods

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

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

Ord Month # 
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 # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Month #

readList :: ReadS [Month] #

readPrec :: ReadPrec Month #

readListPrec :: ReadPrec [Month] #

Show Month # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Month -> ShowS

show :: Month -> String

showList :: [Month] -> ShowS

Prim Month # 
Instance details

Defined in Chronos

Methods

sizeOf# :: Month -> Int# #

alignment# :: Month -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Month #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Month#) #

writeByteArray# :: MutableByteArray# s -> Int# -> Month -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Month -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Month #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Month#) #

writeOffAddr# :: Addr# -> Int# -> Month -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Month -> State# s -> State# s #

Unbox Month # 
Instance details

Defined in Chronos

Vector Vector Month # 
Instance details

Defined in Chronos

MVector MVector Month # 
Instance details

Defined in Chronos

newtype Vector Month # 
Instance details

Defined in Chronos

newtype MVector s Month # 
Instance details

Defined in Chronos

newtype Year #

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

Constructors

Year 

Fields

Instances
Eq Year # 
Instance details

Defined in Chronos

Methods

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

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

Ord Year # 
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 # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Year #

readList :: ReadS [Year] #

readPrec :: ReadPrec Year #

readListPrec :: ReadPrec [Year] #

Show Year # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Year -> ShowS

show :: Year -> String

showList :: [Year] -> ShowS

newtype Offset #

Constructors

Offset 

Fields

Instances
Enum Offset # 
Instance details

Defined in Chronos

Eq Offset # 
Instance details

Defined in Chronos

Methods

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

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

Ord Offset # 
Instance details

Defined in Chronos

Methods

compare :: Offset -> Offset -> Ordering

(<) :: Offset -> Offset -> Bool

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

(>) :: Offset -> Offset -> Bool

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

max :: Offset -> Offset -> Offset

min :: Offset -> Offset -> Offset

Read Offset # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Offset #

readList :: ReadS [Offset] #

readPrec :: ReadPrec Offset #

readListPrec :: ReadPrec [Offset] #

Show Offset # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Offset -> ShowS

show :: Offset -> String

showList :: [Offset] -> ShowS

ToJSON Offset # 
Instance details

Defined in Chronos

ToJSONKey Offset # 
Instance details

Defined in Chronos

FromJSON Offset # 
Instance details

Defined in Chronos

FromJSONKey Offset # 
Instance details

Defined in Chronos

Torsor Offset Int # 
Instance details

Defined in Chronos

Methods

add :: Int -> Offset -> Offset #

difference :: Offset -> Offset -> Int #

newtype Time #

POSIX time with nanosecond resolution.

Constructors

Time 

Fields

Instances
Bounded Time # 
Instance details

Defined in Chronos

Eq Time # 
Instance details

Defined in Chronos

Methods

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

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

Ord Time # 
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 # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Time #

readList :: ReadS [Time] #

readPrec :: ReadPrec Time #

readListPrec :: ReadPrec [Time] #

Show Time # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Time -> ShowS

show :: Time -> String

showList :: [Time] -> ShowS

Hashable Time # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Time -> Int #

hash :: Time -> Int #

ToJSON Time # 
Instance details

Defined in Chronos

FromJSON Time # 
Instance details

Defined in Chronos

Storable Time # 
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 # 
Instance details

Defined in Chronos

Methods

sizeOf# :: Time -> Int# #

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 # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

newtype DayOfWeekMatch a #

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 #

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 #

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

newtype Timespan #

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

Constructors

Timespan 

Fields

Instances
Eq Timespan # 
Instance details

Defined in Chronos

Methods

(==) :: Timespan -> Timespan -> Bool

(/=) :: Timespan -> Timespan -> Bool

Ord Timespan # 
Instance details

Defined in Chronos

Methods

compare :: Timespan -> Timespan -> Ordering

(<) :: Timespan -> Timespan -> Bool

(<=) :: Timespan -> Timespan -> Bool

(>) :: Timespan -> Timespan -> Bool

(>=) :: Timespan -> Timespan -> Bool

max :: Timespan -> Timespan -> Timespan

min :: Timespan -> Timespan -> Timespan

Read Timespan # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Timespan #

readList :: ReadS [Timespan] #

readPrec :: ReadPrec Timespan #

readListPrec :: ReadPrec [Timespan] #

Show Timespan # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Timespan -> ShowS

show :: Timespan -> String

showList :: [Timespan] -> ShowS

Semigroup Timespan # 
Instance details

Defined in Chronos

Methods

(<>) :: Timespan -> Timespan -> Timespan #

sconcat :: NonEmpty Timespan -> Timespan #

stimes :: Integral b => b -> Timespan -> Timespan #

Monoid Timespan # 
Instance details

Defined in Chronos

ToJSON Timespan # 
Instance details

Defined in Chronos

FromJSON Timespan # 
Instance details

Defined in Chronos

Additive Timespan # 
Instance details

Defined in Chronos

Torsor Time Timespan # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

Scaling Timespan Int64 # 
Instance details

Defined in Chronos

Methods

scale :: Int64 -> Timespan -> Timespan #

data SubsecondPrecision #

The precision used when encoding seconds to a human-readable format.

Constructors

SubsecondPrecisionAuto

Rounds to second, millisecond, microsecond, or nanosecond

SubsecondPrecisionFixed !Int

Specify number of places after decimal

data Date #

A date as represented by the Gregorian calendar.

Constructors

Date 
Instances
Enum Date # 
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 # 
Instance details

Defined in Chronos

Methods

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

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

Ord Date # 
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 # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Date #

readList :: ReadS [Date] #

readPrec :: ReadPrec Date #

readListPrec :: ReadPrec [Date] #

Show Date # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Date -> ShowS

show :: Date -> String

showList :: [Date] -> ShowS

Torsor Date Int # 
Instance details

Defined in Chronos

Methods

add :: Int -> Date -> Date #

difference :: Date -> Date -> Int #

data OrdinalDate #

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

Instances
Enum OrdinalDate # 
Instance details

Defined in Chronos

Eq OrdinalDate # 
Instance details

Defined in Chronos

Methods

(==) :: OrdinalDate -> OrdinalDate -> Bool

(/=) :: OrdinalDate -> OrdinalDate -> Bool

Ord OrdinalDate # 
Instance details

Defined in Chronos

Read OrdinalDate # 
Instance details

Defined in Chronos

Show OrdinalDate # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> OrdinalDate -> ShowS

show :: OrdinalDate -> String

showList :: [OrdinalDate] -> ShowS

Torsor OrdinalDate Int # 
Instance details

Defined in Chronos

data MonthDate #

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

Constructors

MonthDate 
Instances
Eq MonthDate # 
Instance details

Defined in Chronos

Methods

(==) :: MonthDate -> MonthDate -> Bool

(/=) :: MonthDate -> MonthDate -> Bool

Ord MonthDate # 
Instance details

Defined in Chronos

Methods

compare :: MonthDate -> MonthDate -> Ordering

(<) :: MonthDate -> MonthDate -> Bool

(<=) :: MonthDate -> MonthDate -> Bool

(>) :: MonthDate -> MonthDate -> Bool

(>=) :: MonthDate -> MonthDate -> Bool

max :: MonthDate -> MonthDate -> MonthDate

min :: MonthDate -> MonthDate -> MonthDate

Read MonthDate # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS MonthDate #

readList :: ReadS [MonthDate] #

readPrec :: ReadPrec MonthDate #

readListPrec :: ReadPrec [MonthDate] #

Show MonthDate # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> MonthDate -> ShowS

show :: MonthDate -> String

showList :: [MonthDate] -> ShowS

data Datetime #

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

Constructors

Datetime 
Instances
Eq Datetime # 
Instance details

Defined in Chronos

Methods

(==) :: Datetime -> Datetime -> Bool

(/=) :: Datetime -> Datetime -> Bool

Ord Datetime # 
Instance details

Defined in Chronos

Methods

compare :: Datetime -> Datetime -> Ordering

(<) :: Datetime -> Datetime -> Bool

(<=) :: Datetime -> Datetime -> Bool

(>) :: Datetime -> Datetime -> Bool

(>=) :: Datetime -> Datetime -> Bool

max :: Datetime -> Datetime -> Datetime

min :: Datetime -> Datetime -> Datetime

Read Datetime # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS Datetime #

readList :: ReadS [Datetime] #

readPrec :: ReadPrec Datetime #

readListPrec :: ReadPrec [Datetime] #

Show Datetime # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Datetime -> ShowS

show :: Datetime -> String

showList :: [Datetime] -> ShowS

ToJSON Datetime # 
Instance details

Defined in Chronos

data OffsetDatetime #

A Datetime with a time zone Offset.

Instances
Eq OffsetDatetime # 
Instance details

Defined in Chronos

Ord OffsetDatetime # 
Instance details

Defined in Chronos

Read OffsetDatetime # 
Instance details

Defined in Chronos

Show OffsetDatetime # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> OffsetDatetime -> ShowS

show :: OffsetDatetime -> String

showList :: [OffsetDatetime] -> ShowS

data TimeOfDay #

A time of day with nanosecond resolution.

Constructors

TimeOfDay 

Fields

Instances
Eq TimeOfDay # 
Instance details

Defined in Chronos

Methods

(==) :: TimeOfDay -> TimeOfDay -> Bool

(/=) :: TimeOfDay -> TimeOfDay -> Bool

Ord TimeOfDay # 
Instance details

Defined in Chronos

Methods

compare :: TimeOfDay -> TimeOfDay -> Ordering

(<) :: TimeOfDay -> TimeOfDay -> Bool

(<=) :: TimeOfDay -> TimeOfDay -> Bool

(>) :: TimeOfDay -> TimeOfDay -> Bool

(>=) :: TimeOfDay -> TimeOfDay -> Bool

max :: TimeOfDay -> TimeOfDay -> TimeOfDay

min :: TimeOfDay -> TimeOfDay -> TimeOfDay

Read TimeOfDay # 
Instance details

Defined in Chronos

Methods

readsPrec :: Int -> ReadS TimeOfDay #

readList :: ReadS [TimeOfDay] #

readPrec :: ReadPrec TimeOfDay #

readListPrec :: ReadPrec [TimeOfDay] #

Show TimeOfDay # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> TimeOfDay -> ShowS

show :: TimeOfDay -> String

showList :: [TimeOfDay] -> ShowS

data DatetimeFormat #

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

Constructors

DatetimeFormat 

Fields

Instances
Eq DatetimeFormat # 
Instance details

Defined in Chronos

Ord DatetimeFormat # 
Instance details

Defined in Chronos

Read DatetimeFormat # 
Instance details

Defined in Chronos

Show DatetimeFormat # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> DatetimeFormat -> ShowS

show :: DatetimeFormat -> String

showList :: [DatetimeFormat] -> ShowS

data OffsetFormat #

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 # 
Instance details

Defined in Chronos

Enum OffsetFormat # 
Instance details

Defined in Chronos

Eq OffsetFormat # 
Instance details

Defined in Chronos

Methods

(==) :: OffsetFormat -> OffsetFormat -> Bool

(/=) :: OffsetFormat -> OffsetFormat -> Bool

Ord OffsetFormat # 
Instance details

Defined in Chronos

Read OffsetFormat # 
Instance details

Defined in Chronos

Show OffsetFormat # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> OffsetFormat -> ShowS

show :: OffsetFormat -> String

showList :: [OffsetFormat] -> ShowS

Generic OffsetFormat # 
Instance details

Defined in Chronos

Associated Types

type Rep OffsetFormat :: Type -> Type

type Rep OffsetFormat # 
Instance details

Defined in Chronos

type Rep OffsetFormat = D1 (MetaData "OffsetFormat" "Chronos" "chronos-1.0.7-BhVazY2rKvdBfduunCFQXE" 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 #

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

Constructors

DatetimeLocale 

Fields

data MeridiemLocale a #

Locale-specific formatting for AM and PM.

Constructors

MeridiemLocale 

Fields

Instances
Eq a => Eq (MeridiemLocale a) # 
Instance details

Defined in Chronos

Methods

(==) :: MeridiemLocale a -> MeridiemLocale a -> Bool

(/=) :: MeridiemLocale a -> MeridiemLocale a -> Bool

Ord a => Ord (MeridiemLocale a) # 
Instance details

Defined in Chronos

Read a => Read (MeridiemLocale a) # 
Instance details

Defined in Chronos

Show a => Show (MeridiemLocale a) # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> MeridiemLocale a -> ShowS

show :: MeridiemLocale a -> String

showList :: [MeridiemLocale a] -> ShowS

data TimeInterval #

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 
Instances
Bounded TimeInterval # 
Instance details

Defined in Chronos

Eq TimeInterval # 
Instance details

Defined in Chronos

Methods

(==) :: TimeInterval -> TimeInterval -> Bool

(/=) :: TimeInterval -> TimeInterval -> Bool

Ord TimeInterval # 
Instance details

Defined in Chronos

Read TimeInterval # 
Instance details

Defined in Chronos

Show TimeInterval # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> TimeInterval -> ShowS

show :: TimeInterval -> String

showList :: [TimeInterval] -> ShowS