-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A time library -- -- A time library @package time @version 1.8 module Data.Time.Calendar.MonthDay -- | Convert month and day in the Gregorian or Julian calendars to day of -- year. First arg is leap year flag. monthAndDayToDayOfYear :: Bool -> Int -> Int -> Int -- | Convert month and day in the Gregorian or Julian calendars to day of -- year. First arg is leap year flag. monthAndDayToDayOfYearValid :: Bool -> Int -> Int -> Maybe Int -- | Convert day of year in the Gregorian or Julian calendars to month and -- day. First arg is leap year flag. dayOfYearToMonthAndDay :: Bool -> Int -> (Int, Int) -- | The length of a given month in the Gregorian or Julian calendars. -- First arg is leap year flag. monthLength :: Bool -> Int -> Int module Data.Time.Calendar.Julian -- | Convert to proleptic Julian year and day format. First element of -- result is year (proleptic Julian calendar), second is the day of the -- year, with 1 for Jan 1, and 365 (or 366 in leap years) for Dec 31. toJulianYearAndDay :: Day -> (Integer, Int) -- | Convert from proleptic Julian year and day format. Invalid day numbers -- will be clipped to the correct range (1 to 365 or 366). fromJulianYearAndDay :: Integer -> Int -> Day -- | Convert from proleptic Julian year and day format. Invalid day numbers -- will return Nothing fromJulianYearAndDayValid :: Integer -> Int -> Maybe Day -- | Show in proleptic Julian year and day format (yyyy-ddd) showJulianYearAndDay :: Day -> String -- | Is this year a leap year according to the proleptic Julian calendar? isJulianLeapYear :: Integer -> Bool -- | Convert to proleptic Julian calendar. First element of result is year, -- second month number (1-12), third day (1-31). toJulian :: Day -> (Integer, Int, Int) -- | Convert from proleptic Julian calendar. First argument is year, second -- month number (1-12), third day (1-31). Invalid values will be clipped -- to the correct range, month first, then day. fromJulian :: Integer -> Int -> Int -> Day -- | Convert from proleptic Julian calendar. First argument is year, second -- month number (1-12), third day (1-31). Invalid values will return -- Nothing. fromJulianValid :: Integer -> Int -> Int -> Maybe Day -- | Show in ISO 8601 format (yyyy-mm-dd) showJulian :: Day -> String -- | The number of days in a given month according to the proleptic Julian -- calendar. First argument is year, second is month. julianMonthLength :: Integer -> Int -> Int -- | Add months, with days past the last day of the month clipped to the -- last day. For instance, 2005-01-30 + 1 month = 2005-02-28. addJulianMonthsClip :: Integer -> Day -> Day -- | Add months, with days past the last day of the month rolling over to -- the next month. For instance, 2005-01-30 + 1 month = 2005-03-02. addJulianMonthsRollOver :: Integer -> Day -> Day -- | Add years, matching month and day, with Feb 29th clipped to Feb 28th -- if necessary. For instance, 2004-02-29 + 2 years = 2006-02-28. addJulianYearsClip :: Integer -> Day -> Day -- | Add years, matching month and day, with Feb 29th rolled over to Mar -- 1st if necessary. For instance, 2004-02-29 + 2 years = 2006-03-01. addJulianYearsRollOver :: Integer -> Day -> Day -- | ISO 8601 Ordinal Date format module Data.Time.Calendar.OrdinalDate -- | Convert to ISO 8601 Ordinal Date format. First element of result is -- year (proleptic Gregoran calendar), second is the day of the year, -- with 1 for Jan 1, and 365 (or 366 in leap years) for Dec 31. toOrdinalDate :: Day -> (Integer, Int) -- | Convert from ISO 8601 Ordinal Date format. Invalid day numbers will be -- clipped to the correct range (1 to 365 or 366). fromOrdinalDate :: Integer -> Int -> Day -- | Convert from ISO 8601 Ordinal Date format. Invalid day numbers return -- Nothing fromOrdinalDateValid :: Integer -> Int -> Maybe Day -- | Show in ISO 8601 Ordinal Date format (yyyy-ddd) showOrdinalDate :: Day -> String -- | Is this year a leap year according to the proleptic Gregorian -- calendar? isLeapYear :: Integer -> Bool -- | Get the number of the Monday-starting week in the year and the day of -- the week. The first Monday is the first day of week 1, any earlier -- days in the year are week 0 (as %W in formatTime). -- Monday is 1, Sunday is 7 (as %u in formatTime). mondayStartWeek :: Day -> (Int, Int) -- | Get the number of the Sunday-starting week in the year and the day of -- the week. The first Sunday is the first day of week 1, any earlier -- days in the year are week 0 (as %U in formatTime). -- Sunday is 0, Saturday is 6 (as %w in formatTime). sundayStartWeek :: Day -> (Int, Int) -- | The inverse of mondayStartWeek. Get a Day given the -- year, the number of the Monday-starting week, and the day of the week. -- The first Monday is the first day of week 1, any earlier days in the -- year are week 0 (as %W in formatTime). fromMondayStartWeek :: Integer -> Int -> Int -> Day fromMondayStartWeekValid :: Integer -> Int -> Int -> Maybe Day -- | The inverse of sundayStartWeek. Get a Day given the year -- and the number of the day of a Sunday-starting week. The first Sunday -- is the first day of week 1, any earlier days in the year are week 0 -- (as %U in formatTime). fromSundayStartWeek :: Integer -> Int -> Int -> Day fromSundayStartWeekValid :: Integer -> Int -> Int -> Maybe Day -- | ISO 8601 Week Date format module Data.Time.Calendar.WeekDate -- | Convert to ISO 8601 Week Date format. First element of result is year, -- second week number (1-53), third day of week (1 for Monday to 7 for -- Sunday). Note that "Week" years are not quite the same as Gregorian -- years, as the first day of the year is always a Monday. The first week -- of a year is the first week to contain at least four days in the -- corresponding Gregorian year. toWeekDate :: Day -> (Integer, Int, Int) -- | Convert from ISO 8601 Week Date format. First argument is year, second -- week number (1-52 or 53), third day of week (1 for Monday to 7 for -- Sunday). Invalid week and day values will be clipped to the correct -- range. fromWeekDate :: Integer -> Int -> Int -> Day -- | Convert from ISO 8601 Week Date format. First argument is year, second -- week number (1-52 or 53), third day of week (1 for Monday to 7 for -- Sunday). Invalid week and day values will return Nothing. fromWeekDateValid :: Integer -> Int -> Int -> Maybe Day -- | Show in ISO 8601 Week Date format as yyyy-Www-d (e.g. "2006-W46-3"). showWeekDate :: Day -> String -- | Fast access to the system clock. module Data.Time.Clock.System -- | The day of the epoch of SystemTime, 1970-01-01 systemEpochDay :: Day -- | SystemTime is time returned by system clock functions. Its -- semantics depends on the clock function, but the epoch is typically -- the beginning of 1970. Note that systemNanoseconds of 1E9 to -- 2E9-1 can be used to represent leap seconds. data SystemTime MkSystemTime :: {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Word32 -> SystemTime [systemSeconds] :: SystemTime -> {-# UNPACK #-} !Int64 [systemNanoseconds] :: SystemTime -> {-# UNPACK #-} !Word32 -- | Map leap-second values to the start of the following second. The -- resulting systemNanoseconds will always be in the range 0 to -- 1E9-1. truncateSystemTimeLeapSecond :: SystemTime -> SystemTime -- | Get the system time, epoch start of 1970 UTC, leap-seconds ignored. -- getSystemTime is typically much faster than -- getCurrentTime. getSystemTime :: IO SystemTime -- | Convert SystemTime to UTCTime, matching zero -- SystemTime to midnight of systemEpochDay UTC. systemToUTCTime :: SystemTime -> UTCTime -- | Convert UTCTime to SystemTime, matching zero -- SystemTime to midnight of systemEpochDay UTC. utcToSystemTime :: UTCTime -> SystemTime -- | Convert SystemTime to AbsoluteTime, matching zero -- SystemTime to midnight of systemEpochDay TAI. systemToTAITime :: SystemTime -> AbsoluteTime -- | POSIX time, if you need to deal with timestamps and the like. Most -- people won't need this module. module Data.Time.Clock.POSIX -- | 86400 nominal seconds in every day posixDayLength :: NominalDiffTime -- | POSIX time is the nominal time since 1970-01-01 00:00 UTC -- -- To convert from a CTime or EpochTime, use -- realToFrac. type POSIXTime = NominalDiffTime posixSecondsToUTCTime :: POSIXTime -> UTCTime utcTimeToPOSIXSeconds :: UTCTime -> POSIXTime -- | Get the current POSIX time from the system clock. getPOSIXTime :: IO POSIXTime -- | Get the current UTCTime from the system clock. getCurrentTime :: IO UTCTime systemToPOSIXTime :: SystemTime -> POSIXTime module Data.Time.Format type NumericPadOption = Maybe Char class FormatTime t formatCharacter :: FormatTime t => Char -> Maybe (TimeLocale -> Maybe NumericPadOption -> Maybe Int -> t -> String) -- | Substitute various time-related information for each %-code in the -- string, as per formatCharacter. -- -- The general form is -- %<modifier><width><specifier>, where -- <modifier> and <width> are optional. -- --

<modifier>

-- -- glibc-style modifiers can be used before the specifier (here marked as -- z): -- -- -- --

<width>

-- -- Width digits can also be used after any modifiers and before the -- specifier (here marked as z), for example: -- -- -- --

<specifier>

-- -- For all types (note these three are done by formatTime, not by -- formatCharacter): -- -- -- --

TimeZone

-- -- For TimeZone (and ZonedTime and UTCTime): -- -- -- --

LocalTime

-- -- For LocalTime (and ZonedTime and UTCTime and -- UniversalTime): -- -- -- --

TimeOfDay

-- -- For TimeOfDay (and LocalTime and ZonedTime and -- UTCTime and UniversalTime): -- -- -- --

UTCTime and ZonedTime

-- -- For UTCTime and ZonedTime: -- -- -- --

Day

-- -- For Day (and LocalTime and ZonedTime and -- UTCTime and UniversalTime): -- -- formatTime :: (FormatTime t) => TimeLocale -> String -> t -> String -- | Parses a time value given a format string. Supports the same %-codes -- as formatTime, including %-, %_ and -- %0 modifiers, however padding widths are not supported. Case -- is not significant in the input string. Some variations in the input -- are accepted: -- -- parseTimeM :: (Monad m, ParseTime t) => Bool -> TimeLocale -> String -> String -> m t -- | Parse a time value given a format string. Fails if the input could not -- be parsed using the given format. See parseTimeM for details. parseTimeOrError :: ParseTime t => Bool -> TimeLocale -> String -> String -> t -- | Parse a time value given a format string. See parseTimeM for -- details. readSTime :: ParseTime t => Bool -> TimeLocale -> String -> ReadS t -- | Parse a time value given a format string. See parseTimeM for -- details. readPTime :: ParseTime t => Bool -> TimeLocale -> String -> ReadP t -- | Deprecated: use "parseTimeM True" instead parseTime :: ParseTime t => TimeLocale -> String -> String -> Maybe t -- | Deprecated: use "parseTimeOrError True" instead readTime :: ParseTime t => TimeLocale -> String -> String -> t -- | Deprecated: use "readSTime True" instead readsTime :: ParseTime t => TimeLocale -> String -> ReadS t -- | The class of types which can be parsed given a UNIX-style time format -- string. class ParseTime t -- | Builds a time value from a parsed input string. If the input does not -- include all the information needed to construct a complete value, any -- missing parts should be taken from 1970-01-01 00:00:00 +0000 (which -- was a Thursday). In the absence of %C or %Y, century -- is 1969 - 2068. buildTime :: ParseTime t => TimeLocale -> [(Char, String)] -> Maybe t data TimeLocale TimeLocale :: [(String, String)] -> [(String, String)] -> (String, String) -> String -> [TimeZone] -> TimeLocale -- | full and abbreviated week days, starting with Sunday [wDays] :: TimeLocale -> [(String, String)] -- | full and abbreviated months [months] :: TimeLocale -> [(String, String)] -- | AM/PM symbols [amPm] :: TimeLocale -> (String, String) -- | formatting strings -- | formatting strings -- | formatting strings -- | formatting strings [dateTimeFmt, dateFmt, timeFmt, time12Fmt] :: TimeLocale -> String -- | time zones known by name [knownTimeZones] :: TimeLocale -> [TimeZone] -- | Locale representing American usage. -- -- knownTimeZones contains only the ten time-zones mentioned in -- RFC 822 sec. 5: "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", -- "PST", "PDT". Note that the parsing functions will regardless parse -- single-letter military time-zones and +HHMM format. defaultTimeLocale :: TimeLocale -- | Construct format string according to ISO-8601. -- -- The Maybe String argument allows to supply an optional time -- specification. E.g.: -- --
--   iso8601DateFormat Nothing            == "%Y-%m-%d"           -- i.e. YYYY-MM-DD
--   iso8601DateFormat (Just "%H:%M:%S")  == "%Y-%m-%dT%H:%M:%S"  -- i.e. YYYY-MM-DDTHH:MM:SS
--   
iso8601DateFormat :: Maybe String -> String -- | Format string according to RFC822. rfc822DateFormat :: String instance Data.Time.Format.FormatTime Data.Time.LocalTime.Internal.LocalTime.LocalTime instance Data.Time.Format.FormatTime Data.Time.LocalTime.Internal.TimeOfDay.TimeOfDay instance Data.Time.Format.FormatTime Data.Time.LocalTime.Internal.ZonedTime.ZonedTime instance Data.Time.Format.FormatTime Data.Time.LocalTime.Internal.TimeZone.TimeZone instance Data.Time.Format.FormatTime Data.Time.Calendar.Days.Day instance Data.Time.Format.FormatTime Data.Time.Clock.Internal.UTCTime.UTCTime instance Data.Time.Format.FormatTime Data.Time.Clock.Internal.UniversalTime.UniversalTime module Data.Time.LocalTime -- | A TimeZone is a whole number of minutes offset from UTC, together with -- a name and a "just for summer" flag. data TimeZone TimeZone :: Int -> Bool -> String -> TimeZone -- | The number of minutes offset from UTC. Positive means local time will -- be later in the day than UTC. [timeZoneMinutes] :: TimeZone -> Int -- | Is this time zone just persisting for the summer? [timeZoneSummerOnly] :: TimeZone -> Bool -- | The name of the zone, typically a three- or four-letter acronym. [timeZoneName] :: TimeZone -> String -- | Text representing the offset of this timezone, such as "-0800" or -- "+0400" (like %z in formatTime). timeZoneOffsetString :: TimeZone -> String -- | Text representing the offset of this timezone, such as "-0800" or -- "+0400" (like %z in formatTime), with arbitrary padding. timeZoneOffsetString' :: Maybe Char -> TimeZone -> String -- | Create a nameless non-summer timezone for this number of minutes. minutesToTimeZone :: Int -> TimeZone -- | Create a nameless non-summer timezone for this number of hours. hoursToTimeZone :: Int -> TimeZone -- | The UTC time zone. utc :: TimeZone -- | Get the local time-zone for a given time (varying as per summertime -- adjustments). getTimeZone :: UTCTime -> IO TimeZone -- | Get the current time-zone. getCurrentTimeZone :: IO TimeZone -- | Time of day as represented in hour, minute and second (with -- picoseconds), typically used to express local time of day. data TimeOfDay TimeOfDay :: Int -> Int -> Pico -> TimeOfDay -- | range 0 - 23 [todHour] :: TimeOfDay -> Int -- | range 0 - 59 [todMin] :: TimeOfDay -> Int -- | Note that 0 <= todSec < 61, accomodating leap seconds. -- Any local minute may have a leap second, since leap seconds happen in -- all zones simultaneously [todSec] :: TimeOfDay -> Pico -- | Hour zero midnight :: TimeOfDay -- | Hour twelve midday :: TimeOfDay makeTimeOfDayValid :: Int -> Int -> Pico -> Maybe TimeOfDay -- | Convert a time of day in UTC to a time of day in some timezone, -- together with a day adjustment. utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) -- | Convert a time of day in some timezone to a time of day in UTC, -- together with a day adjustment. localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) -- | Get the time of day given a time since midnight. Time more than 24h -- will be converted to leap-seconds. timeToTimeOfDay :: DiffTime -> TimeOfDay -- | Get the time since midnight for a given time of day. timeOfDayToTime :: TimeOfDay -> DiffTime -- | Get the time of day given the fraction of a day since midnight. dayFractionToTimeOfDay :: Rational -> TimeOfDay -- | Get the fraction of a day since midnight given a time of day. timeOfDayToDayFraction :: TimeOfDay -> Rational -- | A simple day and time aggregate, where the day is of the specified -- parameter, and the time is a TimeOfDay. Conversion of this (as local -- civil time) to UTC depends on the time zone. Conversion of this (as -- local mean time) to UT1 depends on the longitude. data LocalTime LocalTime :: Day -> TimeOfDay -> LocalTime [localDay] :: LocalTime -> Day [localTimeOfDay] :: LocalTime -> TimeOfDay -- | Get the local time of a UTC time in a time zone. utcToLocalTime :: TimeZone -> UTCTime -> LocalTime -- | Get the UTC time of a local time in a time zone. localTimeToUTC :: TimeZone -> LocalTime -> UTCTime -- | Get the local time of a UT1 time on a particular meridian (in degrees, -- positive is East). ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime -- | Get the UT1 time of a local time on a particular meridian (in degrees, -- positive is East). localTimeToUT1 :: Rational -> LocalTime -> UniversalTime -- | A local time together with a time zone. data ZonedTime ZonedTime :: LocalTime -> TimeZone -> ZonedTime [zonedTimeToLocalTime] :: ZonedTime -> LocalTime [zonedTimeZone] :: ZonedTime -> TimeZone utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime zonedTimeToUTC :: ZonedTime -> UTCTime getZonedTime :: IO ZonedTime utcToLocalZonedTime :: UTCTime -> IO ZonedTime -- | Types and functions for UTC and UT1 module Data.Time.Clock -- | The Modified Julian Date is the day with the fraction of the day, -- measured from UT midnight. It's used to represent UT1, which is time -- as measured by the earth's rotation, adjusted for various wobbles. newtype UniversalTime ModJulianDate :: Rational -> UniversalTime [getModJulianDate] :: UniversalTime -> Rational -- | This is a length of time, as measured by a clock. Conversion functions -- will treat it as seconds. It has a precision of 10^-12 s. data DiffTime -- | Create a DiffTime which represents an integral number of -- seconds. secondsToDiffTime :: Integer -> DiffTime -- | Create a DiffTime from a number of picoseconds. picosecondsToDiffTime :: Integer -> DiffTime -- | Get the number of picoseconds in a DiffTime. diffTimeToPicoseconds :: DiffTime -> Integer -- | This is the simplest representation of UTC. It consists of the day -- number, and a time offset from midnight. Note that if a day has a leap -- second added to it, it will have 86401 seconds. data UTCTime UTCTime :: Day -> DiffTime -> UTCTime -- | the day [utctDay] :: UTCTime -> Day -- | the time from midnight, 0 <= t < 86401s (because of -- leap-seconds) [utctDayTime] :: UTCTime -> DiffTime -- | This is a length of time, as measured by UTC. Conversion functions -- will treat it as seconds. It has a precision of 10^-12 s. It ignores -- leap-seconds, so it's not necessarily a fixed amount of clock time. -- For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 -- day), regardless of whether a leap-second intervened. data NominalDiffTime -- | One day in NominalDiffTime. nominalDay :: NominalDiffTime -- | addUTCTime a b = a + b addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime -- | diffUTCTime a b = a - b diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime -- | Get the current UTCTime from the system clock. getCurrentTime :: IO UTCTime -- | The resolution of getSystemTime, getCurrentTime, -- getPOSIXTime getTime_resolution :: DiffTime -- | TAI and leap-second maps for converting to UTC: most people won't need -- this module. module Data.Time.Clock.TAI -- | AbsoluteTime is TAI, time as measured by a clock. data AbsoluteTime -- | The epoch of TAI, which is 1858-11-17 00:00:00 TAI. taiEpoch :: AbsoluteTime -- | addAbsoluteTime a b = a + b addAbsoluteTime :: DiffTime -> AbsoluteTime -> AbsoluteTime -- | diffAbsoluteTime a b = a - b diffAbsoluteTime :: AbsoluteTime -> AbsoluteTime -> DiffTime taiNominalDayStart :: Day -> AbsoluteTime -- | TAI - UTC during this day. No table is provided, as any program -- compiled with it would become out of date in six months. type LeapSecondMap = Day -> Maybe Int utcDayLength :: LeapSecondMap -> Day -> Maybe DiffTime utcToTAITime :: LeapSecondMap -> UTCTime -> Maybe AbsoluteTime taiToUTCTime :: LeapSecondMap -> AbsoluteTime -> Maybe UTCTime -- | TAI clock, if it exists. Note that it is unlikely to be set correctly, -- without due care and attention. taiClock :: Maybe (DiffTime, IO AbsoluteTime) instance GHC.Show.Show Data.Time.Clock.Internal.AbsoluteTime.AbsoluteTime module Data.Time.Calendar -- | The Modified Julian Day is a standard count of days, with zero being -- the day 1858-11-17. newtype Day ModifiedJulianDay :: Integer -> Day [toModifiedJulianDay] :: Day -> Integer addDays :: Integer -> Day -> Day diffDays :: Day -> Day -> Integer -- | Convert to proleptic Gregorian calendar. First element of result is -- year, second month number (1-12), third day (1-31). toGregorian :: Day -> (Integer, Int, Int) -- | Convert from proleptic Gregorian calendar. First argument is year, -- second month number (1-12), third day (1-31). Invalid values will be -- clipped to the correct range, month first, then day. fromGregorian :: Integer -> Int -> Int -> Day -- | Convert from proleptic Gregorian calendar. First argument is year, -- second month number (1-12), third day (1-31). Invalid values will -- return Nothing fromGregorianValid :: Integer -> Int -> Int -> Maybe Day -- | Show in ISO 8601 format (yyyy-mm-dd) showGregorian :: Day -> String -- | The number of days in a given month according to the proleptic -- Gregorian calendar. First argument is year, second is month. gregorianMonthLength :: Integer -> Int -> Int -- | Add months, with days past the last day of the month clipped to the -- last day. For instance, 2005-01-30 + 1 month = 2005-02-28. addGregorianMonthsClip :: Integer -> Day -> Day -- | Add months, with days past the last day of the month rolling over to -- the next month. For instance, 2005-01-30 + 1 month = 2005-03-02. addGregorianMonthsRollOver :: Integer -> Day -> Day -- | Add years, matching month and day, with Feb 29th clipped to Feb 28th -- if necessary. For instance, 2004-02-29 + 2 years = 2006-02-28. addGregorianYearsClip :: Integer -> Day -> Day -- | Add years, matching month and day, with Feb 29th rolled over to Mar -- 1st if necessary. For instance, 2004-02-29 + 2 years = 2006-03-01. addGregorianYearsRollOver :: Integer -> Day -> Day -- | Is this year a leap year according to the proleptic Gregorian -- calendar? isLeapYear :: Integer -> Bool module Data.Time.Calendar.Easter -- | The next Sunday strictly after a given day. sundayAfter :: Day -> Day -- | Given a year, find the Paschal full moon according to Orthodox -- Christian tradition orthodoxPaschalMoon :: Integer -> Day -- | Given a year, find Easter according to Orthodox Christian tradition orthodoxEaster :: Integer -> Day -- | Given a year, find the Paschal full moon according to the Gregorian -- method gregorianPaschalMoon :: Integer -> Day -- | Given a year, find Easter according to the Gregorian method gregorianEaster :: Integer -> Day module Data.Time