chronos-1.0.4: A performant time library

Safe HaskellNone
LanguageHaskell2010

Chronos

Contents

Synopsis

Functions

Current

now :: IO Time Source #

Get the current time from the system clock.

today :: IO Day Source #

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

tomorrow :: IO Day Source #

Gets the Day of tomorrow.

yesterday :: IO Day Source #

Gets the Day of yesterday.

epoch :: Time Source #

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

Duration

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

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

stopwatch_ :: IO a -> IO Timespan Source #

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

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

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

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

Variant of stopwatch_ that accepts a clock type.

Construction

datetimeFromYmdhms :: 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

timeFromYmdhms :: Int -> Int -> Int -> Int -> Int -> Int -> Time Source #

Conversion

timeToDayTruncate :: Time -> Day Source #

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

dayToTimeMidnight :: Day -> Time Source #

Convert midnight of the given Day to Time.

dayToDate :: Day -> Date Source #

Convert Day to a Date.

dateToDay :: Date -> Day Source #

Convert Date to a Day.

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 #

Format

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

Months

Days of Week

Utility

daysInMonth Source #

Arguments

:: Bool

Is this a leap year?

-> Month

Month of year

-> Int 

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.

UTF-8 ByteString

Time of Day

Text

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

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_YmdHMS :: SubsecondPrecision -> DatetimeFormat -> Datetime -> Builder Source #

This could be written much more efficiently since we know the exact size the resulting Text will be.

UTF-8 ByteString

Offset Datetime

Text

UTF-8 ByteString

Offset

Text

UTF-8 ByteString

Timespan

Text

UTF-8 ByteString

Types

newtype Day Source #

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

Constructors

Day 

Fields

Instances
Enum Day Source # 
Instance details

Defined in Chronos

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

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

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

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

Eq Day Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Day Source # 
Instance details

Defined in Chronos

Methods

compare :: Day -> Day -> Ordering #

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

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

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

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

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Read Day Source # 
Instance details

Defined in Chronos

Show Day Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Hashable Day Source # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Day -> Int #

hash :: Day -> Int #

ToJSON Day Source # 
Instance details

Defined in Chronos

FromJSON Day Source # 
Instance details

Defined in Chronos

Storable Day Source # 
Instance details

Defined in Chronos

Methods

sizeOf :: Day -> Int #

alignment :: Day -> Int #

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

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

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

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

peek :: Ptr Day -> IO Day #

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

Prim Day Source # 
Instance details

Defined in Chronos

Torsor Day Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Day -> Day #

difference :: Day -> Day -> Int #

newtype DayOfWeek Source #

The day of the week.

Constructors

DayOfWeek 

Fields

Instances
Eq DayOfWeek Source # 
Instance details

Defined in Chronos

Ord DayOfWeek Source # 
Instance details

Defined in Chronos

Read DayOfWeek Source # 
Instance details

Defined in Chronos

Show DayOfWeek Source # 
Instance details

Defined in Chronos

Hashable DayOfWeek Source # 
Instance details

Defined in Chronos

newtype DayOfMonth Source #

The day of the month.

Constructors

DayOfMonth 

Fields

Instances
Enum DayOfMonth Source # 
Instance details

Defined in Chronos

Eq DayOfMonth Source # 
Instance details

Defined in Chronos

Ord DayOfMonth Source # 
Instance details

Defined in Chronos

Read DayOfMonth Source # 
Instance details

Defined in Chronos

Show DayOfMonth Source # 
Instance details

Defined in Chronos

Prim DayOfMonth Source # 
Instance details

Defined in Chronos

Unbox DayOfMonth Source # 
Instance details

Defined in Chronos

Vector Vector DayOfMonth Source # 
Instance details

Defined in Chronos

MVector MVector DayOfMonth Source # 
Instance details

Defined in Chronos

data Vector DayOfMonth Source # 
Instance details

Defined in Chronos

data MVector s DayOfMonth Source # 
Instance details

Defined in Chronos

newtype DayOfYear Source #

The day of the year.

Constructors

DayOfYear 

Fields

Instances
Eq DayOfYear Source # 
Instance details

Defined in Chronos

Ord DayOfYear Source # 
Instance details

Defined in Chronos

Read DayOfYear Source # 
Instance details

Defined in Chronos

Show DayOfYear Source # 
Instance details

Defined in Chronos

Prim DayOfYear Source # 
Instance details

Defined in Chronos

newtype Month Source #

The month of the year.

Constructors

Month 

Fields

Instances
Bounded Month Source # 
Instance details

Defined in Chronos

Enum Month Source # 
Instance details

Defined in Chronos

Eq Month Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Month Source # 
Instance details

Defined in Chronos

Methods

compare :: Month -> Month -> Ordering #

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

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

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

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

max :: Month -> Month -> Month #

min :: Month -> Month -> Month #

Read Month Source # 
Instance details

Defined in Chronos

Show Month Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

Prim Month Source # 
Instance details

Defined in Chronos

Unbox Month Source # 
Instance details

Defined in Chronos

Vector Vector Month Source # 
Instance details

Defined in Chronos

MVector MVector Month Source # 
Instance details

Defined in Chronos

data Vector Month Source # 
Instance details

Defined in Chronos

data MVector s Month Source # 
Instance details

Defined in Chronos

newtype Year Source #

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

Constructors

Year 

Fields

Instances
Eq Year Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Year Source # 
Instance details

Defined in Chronos

Methods

compare :: Year -> Year -> Ordering #

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

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

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

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

max :: Year -> Year -> Year #

min :: Year -> Year -> Year #

Read Year Source # 
Instance details

Defined in Chronos

Show Year Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Year -> ShowS #

show :: Year -> String #

showList :: [Year] -> ShowS #

newtype Offset Source #

Constructors

Offset 

Fields

Instances
Enum Offset Source # 
Instance details

Defined in Chronos

Eq Offset Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Offset Source # 
Instance details

Defined in Chronos

Read Offset Source # 
Instance details

Defined in Chronos

Show Offset Source # 
Instance details

Defined in Chronos

ToJSON Offset Source # 
Instance details

Defined in Chronos

ToJSONKey Offset Source # 
Instance details

Defined in Chronos

FromJSON Offset Source # 
Instance details

Defined in Chronos

FromJSONKey Offset Source # 
Instance details

Defined in Chronos

Torsor Offset Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Offset -> Offset #

difference :: Offset -> Offset -> Int #

newtype Time Source #

POSIX time with nanosecond resolution.

Constructors

Time 

Fields

Instances
Eq Time Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Time Source # 
Instance details

Defined in Chronos

Methods

compare :: Time -> Time -> Ordering #

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

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

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

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

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

Read Time Source # 
Instance details

Defined in Chronos

Show Time Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Hashable Time Source # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Time -> Int #

hash :: Time -> Int #

ToJSON Time Source # 
Instance details

Defined in Chronos

FromJSON Time Source # 
Instance details

Defined in Chronos

Storable Time Source # 
Instance details

Defined in Chronos

Methods

sizeOf :: Time -> Int #

alignment :: Time -> Int #

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

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

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

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

peek :: Ptr Time -> IO Time #

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

Prim Time Source # 
Instance details

Defined in Chronos

Torsor Time Timespan Source # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

newtype DayOfWeekMatch a Source #

Constructors

DayOfWeekMatch 

newtype MonthMatch a Source #

Constructors

MonthMatch 

Fields

newtype Timespan Source #

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

Constructors

Timespan 

Fields

Instances
Eq Timespan Source # 
Instance details

Defined in Chronos

Ord Timespan Source # 
Instance details

Defined in Chronos

Read Timespan Source # 
Instance details

Defined in Chronos

Show Timespan Source # 
Instance details

Defined in Chronos

Semigroup Timespan Source # 
Instance details

Defined in Chronos

Monoid Timespan Source # 
Instance details

Defined in Chronos

ToJSON Timespan Source # 
Instance details

Defined in Chronos

FromJSON Timespan Source # 
Instance details

Defined in Chronos

Additive Timespan Source # 
Instance details

Defined in Chronos

Torsor Time Timespan Source # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

Scaling Timespan Int64 Source # 
Instance details

Defined in Chronos

Methods

scale :: Int64 -> Timespan -> Timespan #

data SubsecondPrecision Source #

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 Source #

A date as represented by the Gregorian calendar.

Constructors

Date 
Instances
Enum Date Source # 
Instance details

Defined in Chronos

Methods

succ :: Date -> Date #

pred :: Date -> Date #

toEnum :: Int -> Date #

fromEnum :: Date -> Int #

enumFrom :: Date -> [Date] #

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

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

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

Eq Date Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Date Source # 
Instance details

Defined in Chronos

Methods

compare :: Date -> Date -> Ordering #

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

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

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

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

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

Read Date Source # 
Instance details

Defined in Chronos

Show Date Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

Torsor Date Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Date -> Date #

difference :: Date -> Date -> Int #

data OrdinalDate Source #

The year and number of days elapsed since the beginning it began.

Instances
Enum OrdinalDate Source # 
Instance details

Defined in Chronos

Eq OrdinalDate Source # 
Instance details

Defined in Chronos

Ord OrdinalDate Source # 
Instance details

Defined in Chronos

Read OrdinalDate Source # 
Instance details

Defined in Chronos

Show OrdinalDate Source # 
Instance details

Defined in Chronos

Torsor OrdinalDate Int Source # 
Instance details

Defined in Chronos

data MonthDate Source #

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

Constructors

MonthDate 

data Datetime Source #

A date as represented by the Gregorian calendar and a time of day.

Constructors

Datetime 
Instances
Eq Datetime Source # 
Instance details

Defined in Chronos

Ord Datetime Source # 
Instance details

Defined in Chronos

Read Datetime Source # 
Instance details

Defined in Chronos

Show Datetime Source # 
Instance details

Defined in Chronos

ToJSON Datetime Source # 
Instance details

Defined in Chronos

data TimeOfDay Source #

A time of day with nanosecond resolution.

data OffsetFormat Source #

Formatting settings for a timezone offset.

Constructors

OffsetFormatColonOff

%z (e.g., -0400)

OffsetFormatColonOn

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

OffsetFormatSecondsPrecision

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

OffsetFormatColonAuto

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

Instances
Bounded OffsetFormat Source # 
Instance details

Defined in Chronos

Enum OffsetFormat Source # 
Instance details

Defined in Chronos

Eq OffsetFormat Source # 
Instance details

Defined in Chronos

Ord OffsetFormat Source # 
Instance details

Defined in Chronos

Read OffsetFormat Source # 
Instance details

Defined in Chronos

Show OffsetFormat Source # 
Instance details

Defined in Chronos

Generic OffsetFormat Source # 
Instance details

Defined in Chronos

Associated Types

type Rep OffsetFormat :: * -> * #

type Rep OffsetFormat Source # 
Instance details

Defined in Chronos

type Rep OffsetFormat = D1 (MetaData "OffsetFormat" "Chronos" "chronos-1.0.4-9dKcOj3pGO83zJ4BHb4fid" False) ((C1 (MetaCons "OffsetFormatColonOff" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OffsetFormatColonOn" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OffsetFormatSecondsPrecision" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OffsetFormatColonAuto" PrefixI False) (U1 :: * -> *)))

data DatetimeLocale a Source #

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

Constructors

DatetimeLocale 

Fields

data MeridiemLocale a Source #

Locale-specific formatting for AM and PM.

Constructors

MeridiemLocale 

Fields