chronos-1.0.2: 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 # 

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 # 

Methods

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

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

Ord Day Source # 

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

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Hashable Day Source # 

Methods

hashWithSalt :: Int -> Day -> Int #

hash :: Day -> Int #

ToJSON Day Source # 
FromJSON Day Source # 
Storable Day Source # 

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 # 
Torsor Day Int Source # 

Methods

add :: Int -> Day -> Day #

difference :: Day -> Day -> Int #

newtype DayOfMonth Source #

The day of the month.

Constructors

DayOfMonth 

Fields

Instances

Enum DayOfMonth Source # 
Eq DayOfMonth Source # 
Ord DayOfMonth Source # 
Read DayOfMonth Source # 
Show DayOfMonth Source # 
Prim DayOfMonth Source # 
Unbox DayOfMonth Source # 
Vector Vector DayOfMonth Source # 
MVector MVector DayOfMonth Source # 
data Vector DayOfMonth Source # 
data MVector s DayOfMonth Source # 

newtype DayOfYear Source #

The day of the year.

Constructors

DayOfYear 

Fields

newtype Month Source #

The month of the year.

Constructors

Month 

Fields

Instances

Bounded Month Source # 
Enum Month Source # 
Eq Month Source # 

Methods

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

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

Ord Month Source # 

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

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

Prim Month Source # 
Unbox Month Source # 
Vector Vector Month Source # 
MVector MVector Month Source # 
data Vector Month Source # 
data MVector s Month Source # 

newtype Year Source #

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

Constructors

Year 

Fields

Instances

newtype Offset Source #

Constructors

Offset 

Fields

Instances

Enum Offset Source # 
Eq Offset Source # 

Methods

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

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

Ord Offset Source # 
Read Offset Source # 
Show Offset Source # 
ToJSON Offset Source # 
ToJSONKey Offset Source # 
FromJSON Offset Source # 
FromJSONKey Offset Source # 
Torsor Offset Int Source # 

Methods

add :: Int -> Offset -> Offset #

difference :: Offset -> Offset -> Int #

newtype Time Source #

POSIX time with nanosecond resolution.

Constructors

Time 

Fields

Instances

Eq Time Source # 

Methods

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

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

Ord Time Source # 

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

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Hashable Time Source # 

Methods

hashWithSalt :: Int -> Time -> Int #

hash :: Time -> Int #

ToJSON Time Source # 
FromJSON Time Source # 
Storable Time Source # 

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 # 
Torsor Time Timespan Source # 

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 # 
Ord Timespan Source # 
Read Timespan Source # 
Show Timespan Source # 
Monoid Timespan Source # 
ToJSON Timespan Source # 
FromJSON Timespan Source # 
Additive Timespan Source # 
Torsor Time Timespan Source # 

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

Scaling Timespan Int64 Source # 

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

data OrdinalDate Source #

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

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 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 # 
Enum OffsetFormat Source # 
Eq OffsetFormat Source # 
Ord OffsetFormat Source # 
Read OffsetFormat Source # 
Show OffsetFormat Source # 
Generic OffsetFormat Source # 

Associated Types

type Rep OffsetFormat :: * -> * #

type Rep OffsetFormat Source # 
type Rep OffsetFormat = D1 * (MetaData "OffsetFormat" "Chronos" "chronos-1.0.2-LX5OBW1NR1W5ko6b7nIgd6" 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