-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A faster time library -- @package thyme @version 0.3.5.5 -- | FOR INTERNAL USE ONLY. module Data.Thyme.Internal.Micro newtype Micro Micro :: Int64 -> Micro microQuotRem :: Micro -> Micro -> (Int64, Micro) microDivMod :: Micro -> Micro -> (Int64, Micro) instance HasBasis Micro instance VectorSpace Micro instance AdditiveGroup Micro instance Read Micro instance Show Micro instance Vector Vector Micro instance MVector MVector Micro instance Unbox Micro instance Typeable Micro instance Eq Micro instance Ord Micro instance Data Micro instance Generic Micro instance Enum Micro instance Ix Micro instance NFData Micro instance Bounded Micro instance Random Micro instance Arbitrary Micro instance CoArbitrary Micro instance Datatype D1Micro instance Constructor C1_0Micro module Data.Thyme.Clock.POSIX -- | The nominal length of a POSIX day: precisely 86400 SI seconds. posixDayLength :: NominalDiffTime type POSIXTime = NominalDiffTime posixTime :: Iso' UTCTime POSIXTime getPOSIXTime :: IO POSIXTime module Data.Thyme.Format.Human -- | Display DiffTime or NominalDiffTime in a human-readable -- form. humanTimeDiff :: TimeDiff d => d -> String -- | Display DiffTime or NominalDiffTime in a human-readable -- form. humanTimeDiffs :: TimeDiff d => d -> ShowS -- | Display one UTCTime relative to another, in a human-readable -- form. humanRelTime :: UTCTime -> UTCTime -> String -- | Display one UTCTime relative to another, in a human-readable -- form. humanRelTimes :: UTCTime -> UTCTime -> ShowS -- | Julian or Gregorian. module Data.Thyme.Calendar.MonthDay type Month = Int type DayOfMonth = Int data MonthDay MonthDay :: {-# UNPACK #-} !Month -> {-# UNPACK #-} !DayOfMonth -> MonthDay mdMonth :: MonthDay -> {-# UNPACK #-} !Month mdDay :: MonthDay -> {-# UNPACK #-} !DayOfMonth -- | Convert between day of year in the Gregorian or Julian calendars, and -- month and day of month. First arg is leap year flag. monthDay :: Bool -> Iso' DayOfYear MonthDay monthDayValid :: Bool -> MonthDay -> Maybe DayOfYear monthLength :: Bool -> Month -> Days _mdMonth :: Lens' MonthDay Month _mdDay :: Lens' MonthDay DayOfMonth -- | Types and functions for UTC and UT1. -- -- If you don't care about leap seconds, keep to UTCTime and -- NominalDiffTime for your clock calculations, and you'll be -- fine. -- -- Num, Real, Fractional and RealFrac -- instances for DiffTime and NominalDiffTime are only -- available by importing Data.Thyme.Time. In their stead are -- instances of AdditiveGroup, HasBasis and -- VectorSpace, with Scalar DiffTime ≡ -- Scalar NominalDiffTimeRational. -- -- Using fromSeconds and toSeconds to convert between -- TimeDiffs and other numeric types. If you really must coerce -- between DiffTime and NominalDiffTime, view -- (microseconds . from microseconds). -- -- UTCTime is an instance of AffineSpace, with -- Diff UTCTimeNominalDiffTime. -- -- UTCTime is not Y294K-compliant. Please file a bug report on -- GitHub when this becomes a problem. module Data.Thyme.Clock -- | The principal form of universal time, namely UT1. -- -- UniversalTime is defined by the rotation of the Earth around -- its axis relative to the Sun. Thus the length of a day by this -- definition varies from one to the next, and is never exactly 86400 SI -- seconds unlike TAI or AbsoluteTime. The difference -- between UT1 and UTC is DUT1. data UniversalTime -- | View UniversalTime as a fractional number of days since the -- Modified Julian Date epoch. modJulianDate :: Iso' UniversalTime Rational -- | An absolute time interval as measured by a clock. -- -- DiffTime forms an AdditiveGroup―so can be added using -- ^+^ (or ^-^ for subtraction), and also an instance of -- VectorSpace―so can be scaled using *^, where -- --
--   type Scalar DiffTime = Rational
--   
data DiffTime -- | Coördinated universal time: the most common form of universal -- time for civil timekeeping. It is synchronised with -- AbsoluteTime and both tick in increments of SI seconds, but -- UTC includes occasional leap-seconds so that it does not drift too far -- from UniversalTime. -- -- UTCTime is an instance of AffineSpace, with -- --
--   type Diff UTCTime = NominalDiffTime
--   
-- -- Use .+^ to add (or .-^ to subtract) time intervals of -- type NominalDiffTime, and .-. to get the interval -- between UTCTimes. -- -- data UTCTime -- | Unpacked UTCTime, partly for compatibility with time. data UTCView UTCTime :: {-# UNPACK #-} !Day -> {-# UNPACK #-} !DiffTime -> UTCView utctDay :: UTCView -> {-# UNPACK #-} !Day utctDayTime :: UTCView -> {-# UNPACK #-} !DiffTime -- | View UTCTime as an UTCView, comprising a Day -- along with a DiffTime offset since midnight. -- -- This is an improper lens: utctDayTime offsets outside the range -- of [zeroV, posixDayLength) will carry over into -- the day part, with the expected behaviour. utcTime :: Iso' UTCTime UTCView -- | A time interval as measured by UTC, that does not take leap-seconds -- into account. -- -- For instance, the difference between 23:59:59 and -- 00:00:01 on the following day is always 2 seconds of -- NominalDiffTime, regardless of whether a leap-second took -- place. -- -- NominalDiffTime forms an AdditiveGroup―so can be added -- using ^+^ (or ^-^ for subtraction), and also an instance -- of VectorSpace―so can be scaled using *^, where -- --
--   type Scalar NominalDiffTime = Rational
--   
data NominalDiffTime -- | Get the current UTC time from the system clock. getCurrentTime :: IO UTCTime -- | Time intervals, encompassing both DiffTime and -- NominalDiffTime. -- -- class (HasBasis t, Basis t ~ (), Scalar t ~ Rational) => TimeDiff t microseconds :: TimeDiff t => Iso' t Int64 -- | Convert a time interval to some Fractional type. toSeconds :: (TimeDiff t, Fractional n) => t -> n -- | Make a time interval from some Real type. -- -- fromSeconds :: (Real n, TimeDiff t) => n -> t -- | Type-restricted toSeconds to avoid constraint-defaulting -- warnings. toSeconds' :: TimeDiff t => t -> Rational -- | Type-restricted fromSeconds to avoid constraint-defaulting -- warnings. fromSeconds' :: TimeDiff t => Rational -> t -- | Lens' for the Day component of an UTCTime. _utctDay :: Lens' UTCTime Day -- | Lens' for the time-of-day component of an UTCTime. _utctDayTime :: Lens' UTCTime DiffTime -- | UTCTime is not Y294K-compliant, and Bounded instances -- for the various calendar types reflect this fact. That said, the -- calendar calculations by themselves work perfectly fine for a wider -- range of dates, subject to the size of Int for your platform. module Data.Thyme.Calendar type Years = Int type Months = Int type Days = Int -- | The Modified Julian Day is a standard count of days, with zero being -- the day 1858-11-17. newtype Day ModifiedJulianDay :: Int -> Day toModifiedJulianDay :: Day -> Int modifiedJulianDay :: Iso' Day Int type Year = Int type Month = Int type DayOfMonth = Int data YearMonthDay YearMonthDay :: {-# UNPACK #-} !Year -> {-# UNPACK #-} !Month -> {-# UNPACK #-} !DayOfMonth -> YearMonthDay ymdYear :: YearMonthDay -> {-# UNPACK #-} !Year ymdMonth :: YearMonthDay -> {-# UNPACK #-} !Month ymdDay :: YearMonthDay -> {-# UNPACK #-} !DayOfMonth -- | Gregorian leap year? isLeapYear :: Year -> Bool yearMonthDay :: Iso' OrdinalDate YearMonthDay gregorian :: Iso' Day YearMonthDay gregorianValid :: YearMonthDay -> Maybe Day showGregorian :: Day -> String gregorianMonthLength :: Year -> Month -> Days gregorianMonthsClip :: Months -> YearMonthDay -> YearMonthDay gregorianMonthsRollover :: Months -> YearMonthDay -> YearMonthDay gregorianYearsClip :: Years -> YearMonthDay -> YearMonthDay gregorianYearsRollover :: Years -> YearMonthDay -> YearMonthDay _ymdYear :: Lens' YearMonthDay Year _ymdMonth :: Lens' YearMonthDay Month _ymdDay :: Lens' YearMonthDay DayOfMonth instance CoArbitrary YearMonthDay instance Arbitrary YearMonthDay instance Arbitrary Day instance Random YearMonthDay instance Random Day instance Bounded YearMonthDay instance Bounded Day module Data.Thyme.LocalTime type Minutes = Int type Hours = Int data TimeZone TimeZone :: {-# UNPACK #-} !Minutes -> !Bool -> String -> TimeZone timeZoneMinutes :: TimeZone -> {-# UNPACK #-} !Minutes timeZoneSummerOnly :: TimeZone -> !Bool timeZoneName :: TimeZone -> String -- | Text representing the offset of this timezone, e.g. "-0800" or "+0400" -- (like %z in formatTime) timeZoneOffsetString :: TimeZone -> String -- | Create a nameless non-summer timezone for this number of minutes minutesToTimeZone :: Minutes -> TimeZone -- | Create a nameless non-summer timezone for this number of hours hoursToTimeZone :: Hours -> TimeZone utc :: TimeZone getTimeZone :: UTCTime -> IO TimeZone getCurrentTimeZone :: IO TimeZone type Hour = Int type Minute = Int data TimeOfDay TimeOfDay :: {-# UNPACK #-} !Hour -> {-# UNPACK #-} !Minute -> {-# UNPACK #-} !DiffTime -> TimeOfDay todHour :: TimeOfDay -> {-# UNPACK #-} !Hour todMin :: TimeOfDay -> {-# UNPACK #-} !Minute todSec :: TimeOfDay -> {-# UNPACK #-} !DiffTime minuteLength :: Hour -> Minute -> DiffTime -- | Hour zero midnight :: TimeOfDay -- | Hour twelve midday :: TimeOfDay makeTimeOfDayValid :: Hour -> Minute -> DiffTime -> Maybe TimeOfDay timeOfDay :: Iso' DiffTime TimeOfDay -- | Add some minutes to a TimeOfDay; result comes with a day -- adjustment. addMinutes :: Minutes -> TimeOfDay -> (Days, TimeOfDay) dayFraction :: Iso' TimeOfDay Rational data LocalTime LocalTime :: {-# UNPACK #-} !Day -> {-# UNPACK #-} !TimeOfDay -> LocalTime localDay :: LocalTime -> {-# UNPACK #-} !Day localTimeOfDay :: LocalTime -> {-# UNPACK #-} !TimeOfDay utcLocalTime :: TimeZone -> Iso' UTCTime LocalTime ut1LocalTime :: Rational -> Iso' UniversalTime LocalTime data ZonedTime ZonedTime :: {-# UNPACK #-} !LocalTime -> !TimeZone -> ZonedTime zonedTimeToLocalTime :: ZonedTime -> {-# UNPACK #-} !LocalTime zonedTimeZone :: ZonedTime -> !TimeZone zonedTime :: Iso' (TimeZone, UTCTime) ZonedTime getZonedTime :: IO ZonedTime utcToLocalZonedTime :: UTCTime -> IO ZonedTime _timeZoneMinutes :: Lens' TimeZone Minutes _timeZoneSummerOnly :: Lens' TimeZone Bool _timeZoneName :: Lens' TimeZone String _todHour :: Lens' TimeOfDay Hour _todMin :: Lens' TimeOfDay Minute _todSec :: Lens' TimeOfDay DiffTime _localDay :: Lens' LocalTime Day _localTimeOfDay :: Lens' LocalTime TimeOfDay _zonedTimeToLocalTime :: Lens' ZonedTime LocalTime _zonedTimeZone :: Lens' ZonedTime TimeZone instance Typeable ZonedTime instance Eq ZonedTime instance Ord ZonedTime instance Data ZonedTime instance Generic ZonedTime instance Datatype D1ZonedTime instance Constructor C1_0ZonedTime instance Selector S1_0_0ZonedTime instance Selector S1_0_1ZonedTime instance Show UTCTime instance Show ZonedTime instance CoArbitrary ZonedTime instance Arbitrary ZonedTime instance Random ZonedTime instance Bounded ZonedTime instance NFData ZonedTime instance CoArbitrary LocalTime instance Arbitrary LocalTime instance Random LocalTime instance Bounded LocalTime instance Show LocalTime instance NFData LocalTime instance Vector Vector LocalTime instance MVector MVector LocalTime instance Unbox LocalTime instance Typeable LocalTime instance Eq LocalTime instance Ord LocalTime instance Data LocalTime instance Generic LocalTime instance Datatype D1LocalTime instance Constructor C1_0LocalTime instance Selector S1_0_0LocalTime instance Selector S1_0_1LocalTime instance CoArbitrary TimeOfDay instance Arbitrary TimeOfDay instance Random TimeOfDay instance Bounded TimeOfDay instance Show TimeOfDay instance NFData TimeOfDay instance Vector Vector TimeOfDay instance MVector MVector TimeOfDay instance Unbox TimeOfDay instance Typeable TimeZone instance Typeable TimeOfDay instance Eq TimeZone instance Ord TimeZone instance Data TimeZone instance Generic TimeZone instance Eq TimeOfDay instance Ord TimeOfDay instance Data TimeOfDay instance Generic TimeOfDay instance Datatype D1TimeZone instance Constructor C1_0TimeZone instance Selector S1_0_0TimeZone instance Selector S1_0_1TimeZone instance Selector S1_0_2TimeZone instance Datatype D1TimeOfDay instance Constructor C1_0TimeOfDay instance Selector S1_0_0TimeOfDay instance Selector S1_0_1TimeOfDay instance Selector S1_0_2TimeOfDay instance CoArbitrary TimeZone instance Arbitrary TimeZone instance Random TimeZone instance Bounded TimeZone instance Show TimeZone instance NFData TimeZone -- | ISO 8601 Ordinal Date format module Data.Thyme.Calendar.OrdinalDate type Year = Int -- | Gregorian leap year? isLeapYear :: Year -> Bool type DayOfYear = Int data OrdinalDate OrdinalDate :: {-# UNPACK #-} !Year -> {-# UNPACK #-} !DayOfYear -> OrdinalDate odYear :: OrdinalDate -> {-# UNPACK #-} !Year odDay :: OrdinalDate -> {-# UNPACK #-} !DayOfYear ordinalDate :: Iso' Day OrdinalDate ordinalDateValid :: OrdinalDate -> Maybe Day _odYear :: Lens' OrdinalDate Year _odDay :: Lens' OrdinalDate DayOfYear instance CoArbitrary OrdinalDate instance Arbitrary OrdinalDate instance Random OrdinalDate instance Bounded OrdinalDate -- | Various Week Date formats module Data.Thyme.Calendar.WeekDate type Year = Int type WeekOfYear = Int type DayOfWeek = Int -- | Weeks numbered 01 to 53, where week 01 is the first week that has at -- least 4 days in the new year. Days before week 01 are considered to -- belong to the previous year. data WeekDate WeekDate :: {-# UNPACK #-} !Year -> {-# UNPACK #-} !WeekOfYear -> {-# UNPACK #-} !DayOfWeek -> WeekDate wdYear :: WeekDate -> {-# UNPACK #-} !Year wdWeek :: WeekDate -> {-# UNPACK #-} !WeekOfYear wdDay :: WeekDate -> {-# UNPACK #-} !DayOfWeek weekDate :: Iso' Day WeekDate weekDateValid :: WeekDate -> Maybe Day showWeekDate :: Day -> String -- | Weeks numbered from 0 to 53, starting with the first Sunday of the -- year as the first day of week 1. The last week of a given year and -- week 0 of the next both refer to the same week, but not all -- DayOfWeek are valid. Year coincides with that of -- gregorian. data SundayWeek SundayWeek :: {-# UNPACK #-} !Year -> {-# UNPACK #-} !WeekOfYear -> {-# UNPACK #-} !DayOfWeek -> SundayWeek swYear :: SundayWeek -> {-# UNPACK #-} !Year swWeek :: SundayWeek -> {-# UNPACK #-} !WeekOfYear swDay :: SundayWeek -> {-# UNPACK #-} !DayOfWeek sundayWeek :: Iso' Day SundayWeek sundayWeekValid :: SundayWeek -> Maybe Day -- | Weeks numbered from 0 to 53, starting with the first Monday of the -- year as the first day of week 1. The last week of a given year and -- week 0 of the next both refer to the same week, but not all -- DayOfWeek are valid. Year coincides with that of -- gregorian. data MondayWeek MondayWeek :: {-# UNPACK #-} !Year -> {-# UNPACK #-} !WeekOfYear -> {-# UNPACK #-} !DayOfWeek -> MondayWeek mwYear :: MondayWeek -> {-# UNPACK #-} !Year mwWeek :: MondayWeek -> {-# UNPACK #-} !WeekOfYear mwDay :: MondayWeek -> {-# UNPACK #-} !DayOfWeek mondayWeek :: Iso' Day MondayWeek mondayWeekValid :: MondayWeek -> Maybe Day _wdYear :: Lens' WeekDate Year _wdWeek :: Lens' WeekDate WeekOfYear _wdDay :: Lens' WeekDate DayOfWeek _swYear :: Lens' SundayWeek Year _swWeek :: Lens' SundayWeek WeekOfYear _swDay :: Lens' SundayWeek DayOfWeek _mwYear :: Lens' MondayWeek Year _mwWeek :: Lens' MondayWeek WeekOfYear _mwDay :: Lens' MondayWeek DayOfWeek instance CoArbitrary MondayWeek instance CoArbitrary SundayWeek instance CoArbitrary WeekDate instance Arbitrary MondayWeek instance Arbitrary SundayWeek instance Arbitrary WeekDate instance Random MondayWeek instance Random SundayWeek instance Random WeekDate instance Bounded MondayWeek instance Bounded SundayWeek instance Bounded WeekDate module Data.Thyme.Calendar.WeekdayOfMonth type Year = Int type Month = Int type DayOfWeek = Int data WeekdayOfMonth WeekdayOfMonth :: {-# UNPACK #-} !Year -> {-# UNPACK #-} !Month -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !DayOfWeek -> WeekdayOfMonth womYear :: WeekdayOfMonth -> {-# UNPACK #-} !Year womMonth :: WeekdayOfMonth -> {-# UNPACK #-} !Month -- | ±1–5, negative means n-th last womNth :: WeekdayOfMonth -> {-# UNPACK #-} !Int womDayOfWeek :: WeekdayOfMonth -> {-# UNPACK #-} !DayOfWeek weekdayOfMonth :: Iso' Day WeekdayOfMonth weekdayOfMonthValid :: WeekdayOfMonth -> Maybe Day _womYear :: Lens' WeekdayOfMonth Year _womMonth :: Lens' WeekdayOfMonth Month _womNth :: Lens' WeekdayOfMonth Int _womDayOfWeek :: Lens' WeekdayOfMonth DayOfWeek instance CoArbitrary WeekdayOfMonth instance Arbitrary WeekdayOfMonth instance Random WeekdayOfMonth instance Bounded WeekdayOfMonth instance NFData WeekdayOfMonth instance Vector Vector WeekdayOfMonth instance MVector MVector WeekdayOfMonth instance Unbox WeekdayOfMonth instance Typeable WeekdayOfMonth instance Eq WeekdayOfMonth instance Ord WeekdayOfMonth instance Data WeekdayOfMonth instance Generic WeekdayOfMonth instance Show WeekdayOfMonth instance Datatype D1WeekdayOfMonth instance Constructor C1_0WeekdayOfMonth instance Selector S1_0_0WeekdayOfMonth instance Selector S1_0_1WeekdayOfMonth instance Selector S1_0_2WeekdayOfMonth instance Selector S1_0_3WeekdayOfMonth module Data.Thyme.Clock.TAI data AbsoluteTime -- | The epoch of TAI, which is 1858-11-17 00:00:00 TAI. taiEpoch :: AbsoluteTime type LeapSecondTable = Either UTCTime AbsoluteTime -> DiffTime utcDayLength :: LeapSecondTable -> Day -> DiffTime absoluteTime :: LeapSecondTable -> Iso' UTCTime AbsoluteTime -- | tai-utc.dat from -- http://maia.usno.navy.mil/ser7/tai-utc.dat parseTAIUTCDAT :: ByteString -> LeapSecondTable instance AffineSpace AbsoluteTime instance Show AbsoluteTime instance Vector Vector AbsoluteTime instance MVector MVector AbsoluteTime instance Unbox AbsoluteTime instance Typeable AbsoluteTime instance Eq AbsoluteTime instance Ord AbsoluteTime instance Data AbsoluteTime instance Generic AbsoluteTime instance Enum AbsoluteTime instance Ix AbsoluteTime instance NFData AbsoluteTime instance Bounded AbsoluteTime instance Random AbsoluteTime instance Arbitrary AbsoluteTime instance CoArbitrary AbsoluteTime instance Datatype D1AbsoluteTime instance Constructor C1_0AbsoluteTime module Data.Thyme.Format class FormatTime t showsTime :: FormatTime t => TimeLocale -> t -> (Char -> ShowS) -> Char -> ShowS formatTime :: FormatTime t => TimeLocale -> String -> t -> String class ParseTime t buildTime :: ParseTime t => TimeParse -> t parseTime :: ParseTime t => TimeLocale -> String -> String -> Maybe t readTime :: ParseTime t => TimeLocale -> String -> String -> t readsTime :: ParseTime t => TimeLocale -> String -> ReadS t data TimeParse TimeParse :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Month -> {-# UNPACK #-} !WeekOfYear -> {-# UNPACK #-} !DayOfMonth -> {-# UNPACK #-} !DayOfYear -> {-# UNPACK #-} !DayOfWeek -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Hour -> {-# UNPACK #-} !Minute -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !DiffTime -> {-# UNPACK #-} !POSIXTime -> !TimeZone -> TimeParse tpCentury :: TimeParse -> {-# UNPACK #-} !Int tpCenturyYear :: TimeParse -> {-# UNPACK #-} !Int tpMonth :: TimeParse -> {-# UNPACK #-} !Month tpWeekOfYear :: TimeParse -> {-# UNPACK #-} !WeekOfYear tpDayOfMonth :: TimeParse -> {-# UNPACK #-} !DayOfMonth tpDayOfYear :: TimeParse -> {-# UNPACK #-} !DayOfYear tpDayOfWeek :: TimeParse -> {-# UNPACK #-} !DayOfWeek tpFlags :: TimeParse -> {-# UNPACK #-} !Int tpHour :: TimeParse -> {-# UNPACK #-} !Hour tpMinute :: TimeParse -> {-# UNPACK #-} !Minute tpSecond :: TimeParse -> {-# UNPACK #-} !Int tpSecFrac :: TimeParse -> {-# UNPACK #-} !DiffTime tpPOSIXTime :: TimeParse -> {-# UNPACK #-} !POSIXTime tpTimeZone :: TimeParse -> !TimeZone -- | Time Parser for UTF-8 encoded ByteStrings. -- -- Attoparsec easily beats any String parser out there, but we do -- have to be careful to convert the input to UTF-8 ByteStrings. timeParser :: TimeLocale -> String -> Parser TimeParse instance Read UTCView instance Enum TimeFlag instance Show TimeFlag instance Show TimeParse instance ParseTime AbsoluteTime instance ParseTime UniversalTime instance ParseTime UTCTime instance ParseTime ZonedTime instance ParseTime TimeZone instance ParseTime Day instance ParseTime LocalTime instance ParseTime MondayWeek instance ParseTime SundayWeek instance ParseTime WeekDate instance ParseTime OrdinalDate instance ParseTime MonthDay instance ParseTime YearMonthDay instance ParseTime TimeOfDay instance Read UTCTime instance Read ZonedTime instance Read LocalTime instance Read TimeOfDay instance Read Day instance FormatTime AbsoluteTime instance FormatTime UniversalTime instance FormatTime UTCTime instance FormatTime ZonedTime instance FormatTime TimeZone instance FormatTime Day instance FormatTime LocalTime instance FormatTime MondayWeek instance FormatTime SundayWeek instance FormatTime WeekDate instance FormatTime OrdinalDate instance FormatTime MonthDay instance FormatTime YearMonthDay instance FormatTime TimeOfDay -- | Thyme is a rewrite of the fine time library, with a -- particular focus on performance for applications that make heavy use -- of timestamps. For example, UTCTime is represented with μs -- precision as an Int64, which gives a usable range from -- -290419-11-07 19:59:05.224192 UTC to 294135-11-26 -- 04:00:54.775807 UTC in the future. -- -- Conversions are provided as Iso's from the lens -- package, while AdditiveGroup, VectorSpace and -- AffineSpace from vector-space allow for more principled -- operations instead of Num, Fractional & al. -- -- Thyme uses strict and unpacked tuples throughout, e.g. -- YearMonthDay or WeekDate. Descriptive Int -- synonyms such as Year and DayOfMonth are also provided. -- -- On platforms where Int is 64-bits wide, types with an -- Enum instance can be used as Keys for IntMap, -- preferably via the EnumMap wrapper provided by -- http://hackage.haskell.org/package/enummapset-th. In any case -- the Ord instances are much faster, if you must use Map. -- -- Data.Thyme.Time is a drop-in compatibility module for existing -- code. module Data.Thyme -- | Instances of FromJSON and ToJSON for UTCTime and -- ZonedTime, along with a newtype wrapper DotNetTime. module Data.Thyme.Format.Aeson -- | A newtype wrapper for UTCTime that uses the same non-standard -- serialization format as Microsoft .NET, whose System.DateTime -- type is by default serialized to JSON as in the following example: -- --
--   /Date(1302547608878)/
--   
-- -- The number represents milliseconds since the Unix epoch. newtype DotNetTime DotNetTime :: UTCTime -> DotNetTime fromDotNetTime :: DotNetTime -> UTCTime instance Typeable DotNetTime instance Eq DotNetTime instance Ord DotNetTime instance Read DotNetTime instance Show DotNetTime instance FormatTime DotNetTime instance FromJSON UTCTime instance ToJSON UTCTime instance FromJSON ZonedTime instance ToJSON ZonedTime instance FromJSON DotNetTime instance ToJSON DotNetTime -- | This module provides just the compatibility wrappers for the things -- that thyme does differently from time. No -- RealFrac instances for DiffTime nor -- NominalDiffTime, nor other riffraff. module Data.Thyme.Time.Core class Thyme a b | b -> a thyme :: Thyme a b => Iso' a b toThyme :: Thyme a b => a -> b fromThyme :: Thyme a b => b -> a addDays :: Days -> Day -> Day diffDays :: Day -> Day -> Days toGregorian :: Day -> (Year, Month, DayOfMonth) fromGregorian :: Year -> Month -> DayOfMonth -> Day fromGregorianValid :: Year -> Month -> DayOfMonth -> Maybe Day addGregorianMonthsClip :: Months -> Day -> Day addGregorianMonthsRollover :: Months -> Day -> Day addGregorianYearsClip :: Years -> Day -> Day addGregorianYearsRollover :: Years -> Day -> Day dayOfYearToMonthAndDay :: Bool -> DayOfYear -> (Month, DayOfMonth) monthAndDayToDayOfYear :: Bool -> Month -> DayOfMonth -> DayOfYear monthAndDayToDayOfYearValid :: Bool -> Month -> DayOfMonth -> Maybe DayOfYear toOrdinalDate :: Day -> (Year, DayOfYear) fromOrdinalDate :: Year -> DayOfYear -> Day fromOrdinalDateValid :: Year -> DayOfYear -> Maybe Day sundayStartWeek :: Day -> (Year, WeekOfYear, DayOfWeek) fromSundayStartWeek :: Year -> WeekOfYear -> DayOfWeek -> Day fromSundayStartWeekValid :: Year -> WeekOfYear -> DayOfWeek -> Maybe Day mondayStartWeek :: Day -> (Year, WeekOfYear, DayOfWeek) fromMondayStartWeek :: Year -> WeekOfYear -> DayOfWeek -> Day fromMondayStartWeekValid :: Year -> WeekOfYear -> DayOfWeek -> Maybe Day toWeekDate :: Day -> (Year, WeekOfYear, DayOfWeek) fromWeekDate :: Year -> WeekOfYear -> DayOfWeek -> Day fromWeekDateValid :: Year -> WeekOfYear -> DayOfWeek -> Maybe Day getModJulianDate :: UniversalTime -> Rational -- | Replacement for ModJulianDate. mkModJulianDate :: Rational -> UniversalTime secondsToDiffTime :: Int64 -> DiffTime picosecondsToDiffTime :: Int64 -> DiffTime mkUTCTime :: Day -> DiffTime -> UTCTime unUTCTime :: UTCTime -> UTCView addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime toMicroseconds :: TimeDiff t => t -> Int64 fromMicroseconds :: TimeDiff t => Int64 -> t posixSecondsToUTCTime :: POSIXTime -> UTCTime utcTimeToPOSIXSeconds :: UTCTime -> POSIXTime addAbsoluteTime :: DiffTime -> AbsoluteTime -> AbsoluteTime diffAbsoluteTime :: AbsoluteTime -> AbsoluteTime -> DiffTime utcToTAITime :: LeapSecondTable -> UTCTime -> AbsoluteTime taiToUTCTime :: LeapSecondTable -> AbsoluteTime -> UTCTime utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Days, TimeOfDay) localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Days, TimeOfDay) timeToTimeOfDay :: DiffTime -> TimeOfDay timeOfDayToTime :: TimeOfDay -> DiffTime dayFractionToTimeOfDay :: Rational -> TimeOfDay timeOfDayToDayFraction :: TimeOfDay -> Rational utcToLocalTime :: TimeZone -> UTCTime -> LocalTime localTimeToUTC :: TimeZone -> LocalTime -> UTCTime ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime localTimeToUT1 :: Rational -> LocalTime -> UniversalTime utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime zonedTimeToUTC :: ZonedTime -> UTCTime instance Thyme ZonedTime ZonedTime instance Thyme LocalTime LocalTime instance Thyme TimeOfDay TimeOfDay instance Thyme TimeZone TimeZone instance Thyme AbsoluteTime AbsoluteTime instance Thyme UTCTime UTCTime instance Thyme UTCTime UTCView instance Thyme NominalDiffTime NominalDiffTime instance Thyme DiffTime DiffTime instance Thyme UniversalTime UniversalTime instance Thyme Day Day -- | This module provides compatibility instances and wrappers for the -- things that thyme does differently from time, and -- allows it to be used as a drop-in replacement for the latter, with the -- exceptions noted below: -- -- -- -- You shouldn't need to use lens or vector-space -- directly if you don't want to. However if you do use -- vector-space and wish to avoid the RealFrac instances -- for DiffTime and NominalDiffTime, import -- Data.Thyme.Time.Core instead. -- -- Anything else is probably not intentional, and you should either -- contact me via IRC or file an issue at -- https://github.com/liyang/thyme/issues. module Data.Thyme.Time instance RealFrac NominalDiffTime instance Fractional NominalDiffTime instance Real NominalDiffTime instance Num NominalDiffTime instance RealFrac DiffTime instance Fractional DiffTime instance Real DiffTime instance Num DiffTime instance RealFrac Micro instance Fractional Micro instance Real Micro instance Num Micro