Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Formatting and parsing for dates and times.
Synopsis
- class FormatTime t where
- formatTime :: FormatTime t => TimeLocale -> String -> t -> String
- class ParseTime t where
- 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 {
- tpCentury :: !Int
- tpCenturyYear :: !Int
- tpMonth :: !Month
- tpWeekOfYear :: !WeekOfYear
- tpDayOfMonth :: !DayOfMonth
- tpDayOfYear :: !DayOfYear
- tpDayOfWeek :: !DayOfWeek
- tpFlags :: !Int
- tpHour :: !Hour
- tpMinute :: !Minute
- tpSecond :: !Int
- tpSecFrac :: !DiffTime
- tpPOSIXTime :: !POSIXTime
- tpTimeZone :: !TimeZone
- timeParser :: TimeLocale -> String -> Parser TimeParse
- data TimeLocale = TimeLocale {}
- defaultTimeLocale :: TimeLocale
Formatting Date/Time to String
class FormatTime t where Source #
All instances of this class may be formatted by formatTime
.
Instances
:: FormatTime t | |
=> TimeLocale | Locale for formatting. |
-> String | Template spec string. |
-> t |
|
-> String |
Format a FormatTime
instance value according to a template string.
These formatting template codes are intended to be compatible with
glibc
strftime()
function, following Data.Time.Format, which
follows formatCalendarTime
from the old-time
package.
Codes which differ from strftime()
are marked as
EXTENSION.
Show/Parse template string spec
For all types
%%
- literal
"%"
For TimeZone
(and ZonedTime
and UTCTime
):
%z
- RFC 822/ISO 8601:1988 style numeric time zone (e.g.,
"-0600"
or"+0100"
)
%N
- ISO 8601 style numeric time zone (e.g.,
"-06:00"
or"+01:00"
) EXTENSION %Z
- timezone name
For LocalTime
(and ZonedTime
and UTCTime
and UniversalTime
)
%c
- The preferred calendar time representation for the current locale. As
dateTimeFmt
locale
(e.g.%a %b %e %H:%M:%S %Z %Y
)
For TimeOfDay
(and LocalTime
and ZonedTime
and UTCTime
and UniversalTime
)
%R
- same as
%H:%M
%T
- same as
%H:%M:%S
%X
- The preferred time of day representation for the current locale. As
timeFmt
locale
(e.g.%H:%M:%S
) %r
- The complete calendar time using the AM/PM format of the current locale. As
time12Fmt
locale
(e.g.%I:%M:%S %p
) %P
- day-half of day from (
amPm
locale
), converted to lowercase,"am"
,"pm"
%p
- day-half of day from (
amPm
locale
),"AM"
,"PM"
%H
- hour of day (24-hour), 0-padded to two chars,
"00"
–"23"
%k
- hour of day (24-hour), space-padded to two chars,
" 0"
–"23"
%I
- hour of day-half (12-hour), 0-padded to two chars,
"01"
–"12"
%l
- hour of day-half (12-hour), space-padded to two chars,
" 1"
–"12"
%M
- minute of hour, 0-padded to two chars,
"00"
–"59"
%S
- second of minute (without decimal part), 0-padded to two chars,
"00"
–"60"
%q
- picosecond of second, 0-padded to twelve chars,
"000000000000"
–"999999999999"
. EXTENSION %v
- microsecond of second, 0-padded to six chars,
"000000"
–"999999"
. EXTENSION %Q
- decimal point and fraction of second, up to 6 second decimals, without trailing zeros.
For a whole number of seconds,
%Q
produces the empty string. EXTENSION
For UTCTime
%s
- number of whole seconds since the Unix epoch. For times before
the Unix epoch, this is a negative number. Note that in
%s.%q
and%s%Q
the decimals are positive, not negative. For example, 0.9 seconds before the Unix epoch is formatted as"-1.1"
with%s%Q
.
For Day
(and LocalTime
and ZonedTime
and UTCTime
and UniversalTime
)
%D
- same as
%m/%d/%y
%F
- same as
%Y-%m-%d
%x
- as
dateFmt
locale
(e.g.%m/%d/%y
) %Y
- year, no padding.
%y
- year of century, 0-padded to two chars,
"00"
–"99"
%C
- century, no padding.
%B
- month name, long form (
fst
frommonths
locale
),"January"
–"December"
%b
,%h
- month name, short form (
snd
frommonths
locale
),"Jan"
–"Dec"
%m
- month of year, 0-padded to two chars,
"01"
–"12"
%d
- day of month, 0-padded to two chars,
"01"
–"31"
%e
- day of month, space-padded to two chars,
" 1"
–"31"
%j
- day of year, 0-padded to three chars,
"001"
–"366"
%G
- year for Week Date format, no padding.
%g
- year of century for Week Date format, 0-padded to two chars,
"00"
–"99"
%f
- century for Week Date format, no padding. EXTENSION
%V
- week of year for Week Date format, 0-padded to two chars,
"01"
–"53"
%u
- day of week for Week Date format,
"1"
–"7"
%a
- day of week, short form (
snd
fromwDays
locale
),"Sun"
–"Sat"
%A
- day of week, long form (
fst
fromwDays
locale
),"Sunday"
–"Saturday"
%U
- week of year where weeks start on Sunday (as
sundayStartWeek
), 0-padded to two chars,"00"
–"53"
%w
- day of week number,
"0"
(= Sunday) –"6"
(= Saturday) %W
- week of year where weeks start on Monday (as
mondayStartWeek
), 0-padded to two chars,"00"
–"53"
Examples
ISO 8601
>formatTime
defaultTimeLocale
"%Y-%m-%dT%H:%M:%S%N" $mkUTCTime
2015 1 15 12 34 56.78 "2015-01-15T12:34:56+00:00"
RFC822
>formatTime
defaultTimeLocale
"%a, %_d %b %Y %H:%M:%S %Z" $mkUTCTime
2015 1 15 12 34 56.78 "Thu, 15 Jan 2015 12:34:56 UTC"
YYYY-MM-DD hh:mm:ss.000000
>formatTime
defaultTimeLocale
"%Y-%m-%d %H:%M:%S.%v" $mkUTCTime
2015 1 15 12 34 56.78 "2015-01-15 12:34:56.780000"
Parsing Date/Time from String
class ParseTime t where Source #
Instances
ParseTime Day Source # | |
ParseTime MondayWeek Source # | |
Defined in Data.Thyme.Format buildTime :: TimeParse -> MondayWeek Source # | |
ParseTime MonthDay Source # | |
ParseTime OrdinalDate Source # | |
Defined in Data.Thyme.Format buildTime :: TimeParse -> OrdinalDate Source # | |
ParseTime SundayWeek Source # | |
Defined in Data.Thyme.Format buildTime :: TimeParse -> SundayWeek Source # | |
ParseTime WeekDate Source # | |
ParseTime YearMonthDay Source # | |
Defined in Data.Thyme.Format buildTime :: TimeParse -> YearMonthDay Source # | |
ParseTime UTCTime Source # | |
ParseTime UniversalTime Source # | |
Defined in Data.Thyme.Format buildTime :: TimeParse -> UniversalTime Source # | |
ParseTime AbsoluteTime Source # | |
Defined in Data.Thyme.Format buildTime :: TimeParse -> AbsoluteTime Source # | |
ParseTime LocalTime Source # | |
ParseTime TimeOfDay Source # | |
ParseTime TimeZone Source # | |
ParseTime ZonedTime Source # | |
:: ParseTime t | |
=> TimeLocale | Locale. |
-> String | Parser template spec string. See |
-> String | String value to be parsed as a |
-> Maybe t |
Parse a string as a ParseTime
instance value.
Return Nothing
if parsing fails.
Examples
ISO 8601
>parseTime
defaultTimeLocale
"%Y-%m-%dT%H:%M:%S%N" "2015-01-15T12:34:56+00:00" ::Maybe
UTCTime
Just 2015-01-15 12:34:56 UTC >parseTime
defaultTimeLocale
"%Y-%m-%dT%H:%M:%S%N" "2015-01-15T12:34:56-12:00" ::Maybe
UTCTime
Just 2015-01-16 00:34:56 UTC
YYYY-MM-DD hh:mm:ss.0
>parseTime
defaultTimeLocale
"%Y-%m-%d %H:%M:%S%Q" "2015-01-15 12:34:56.78" ::Maybe
UTCTime
Just 2015-01-15 12:34:56.78 UTC
:: ParseTime t | |
=> TimeLocale | Locale. |
-> String | Parser template spec string. See |
-> String | String value to be parsed as a |
-> t |
:: ParseTime t | |
=> TimeLocale | Locale. |
-> String | Parser template spec string. See |
-> ReadS t |
Unconstituted date-time for parsing.
TimeParse | |
|
:: TimeLocale | Locale. |
-> String | Parser template spec string. See |
-> Parser TimeParse |
Time Locale
data TimeLocale #
TimeLocale | |
|
Instances
Show TimeLocale | |
Defined in Data.Time.Format.Locale showsPrec :: Int -> TimeLocale -> ShowS # show :: TimeLocale -> String # showList :: [TimeLocale] -> ShowS # | |
Eq TimeLocale | |
Defined in Data.Time.Format.Locale (==) :: TimeLocale -> TimeLocale -> Bool # (/=) :: TimeLocale -> TimeLocale -> Bool # | |
Ord TimeLocale | |
Defined in Data.Time.Format.Locale compare :: TimeLocale -> TimeLocale -> Ordering # (<) :: TimeLocale -> TimeLocale -> Bool # (<=) :: TimeLocale -> TimeLocale -> Bool # (>) :: TimeLocale -> TimeLocale -> Bool # (>=) :: TimeLocale -> TimeLocale -> Bool # max :: TimeLocale -> TimeLocale -> TimeLocale # min :: TimeLocale -> TimeLocale -> TimeLocale # |
defaultTimeLocale :: TimeLocale #
Locale representing American usage.
knownTimeZones
contains only the ten time-zones mentioned in RFC 802 sec. 5:
"UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", "PDT".
Note that the parsing functions will regardless parse "UTC", single-letter military time-zones, and +HHMM format.