Safe Haskell | None |
---|---|
Language | Haskell2010 |
Date parsing and utilities for hledger.
For date and time values, we use the standard Day and UTCTime types.
A SmartDate
is a date which may be partially-specified or relative.
Eg 2008/12/31, but also 2008/12, 12/31, tomorrow, last week, next year.
We represent these as a triple of strings like ("2008","12",""),
("","","tomorrow"), ("","last","week").
A DateSpan
is the span of time between two specific calendar dates, or
an open-ended span where one or both dates are unspecified. (A date span
with both ends unspecified matches all dates.)
An Interval
is ledger's "reporting interval" - weekly, monthly,
quarterly, etc.
Period
will probably replace DateSpan in due course.
- getCurrentDay :: IO Day
- getCurrentMonth :: IO Int
- getCurrentYear :: IO Integer
- nulldate :: Day
- spanContainsDate :: DateSpan -> Day -> Bool
- periodContainsDate :: Period -> Day -> Bool
- parsedateM :: String -> Maybe Day
- parsedate :: String -> Day
- showDate :: Day -> String
- showDateSpan :: DateSpan -> String
- elapsedSeconds :: Fractional a => UTCTime -> UTCTime -> a
- prevday :: Day -> Day
- parsePeriodExpr :: Day -> Text -> Either (ParseError Char MPErr) (Interval, DateSpan)
- nulldatespan :: DateSpan
- failIfInvalidYear :: Monad m => String -> m ()
- failIfInvalidMonth :: Monad m => String -> m ()
- failIfInvalidDay :: Monad m => String -> m ()
- datesepchar :: TextParser m Char
- datesepchars :: [Char]
- spanStart :: DateSpan -> Maybe Day
- spanEnd :: DateSpan -> Maybe Day
- spansSpan :: [DateSpan] -> DateSpan
- spanIntersect :: DateSpan -> DateSpan -> DateSpan
- spansIntersect :: [DateSpan] -> DateSpan
- spanDefaultsFrom :: DateSpan -> DateSpan -> DateSpan
- spanUnion :: DateSpan -> DateSpan -> DateSpan
- spansUnion :: [DateSpan] -> DateSpan
- smartdate :: SimpleTextParser SmartDate
- splitSpan :: Interval -> DateSpan -> [DateSpan]
- fixSmartDate :: Day -> SmartDate -> Day
- fixSmartDateStr :: Day -> Text -> String
- fixSmartDateStrEither :: Day -> Text -> Either (ParseError Char MPErr) String
- fixSmartDateStrEither' :: Day -> Text -> Either (ParseError Char MPErr) Day
- daysInSpan :: DateSpan -> Maybe Integer
- maybePeriod :: Day -> Text -> Maybe (Interval, DateSpan)
- mkdatespan :: String -> String -> DateSpan
Misc date handling utilities
getCurrentDay :: IO Day Source #
Get the current local date.
getCurrentMonth :: IO Int Source #
Get the current local month number.
getCurrentYear :: IO Integer Source #
Get the current local year.
periodContainsDate :: Period -> Day -> Bool Source #
Does the period include the given date ? (Here to avoid import cycle).
parsedate :: String -> Day Source #
Parse a YYYY-MM-DD or YYYYMMDD date string to a Day, or raise an error. For testing/debugging.
>>>
parsedate "2008/02/03"
2008-02-03
showDateSpan :: DateSpan -> String Source #
Render a datespan as a display string, abbreviating into a compact form if possible.
elapsedSeconds :: Fractional a => UTCTime -> UTCTime -> a Source #
parsePeriodExpr :: Day -> Text -> Either (ParseError Char MPErr) (Interval, DateSpan) Source #
Parse a period expression to an Interval and overall DateSpan using the provided reference date, or return a parse error.
failIfInvalidYear :: Monad m => String -> m () Source #
failIfInvalidMonth :: Monad m => String -> m () Source #
failIfInvalidDay :: Monad m => String -> m () Source #
datesepchar :: TextParser m Char Source #
datesepchars :: [Char] Source #
spansSpan :: [DateSpan] -> DateSpan Source #
Get overall span enclosing multiple sequentially ordered spans.
spanIntersect :: DateSpan -> DateSpan -> DateSpan Source #
Calculate the intersection of two datespans.
spansIntersect :: [DateSpan] -> DateSpan Source #
Calculate the intersection of a number of datespans.
spanDefaultsFrom :: DateSpan -> DateSpan -> DateSpan Source #
Fill any unspecified dates in the first span with the dates from the second one. Sort of a one-way spanIntersect.
spansUnion :: [DateSpan] -> DateSpan Source #
Calculate the union of a number of datespans.
smartdate :: SimpleTextParser SmartDate Source #
Parse a date in any of the formats allowed in ledger's period expressions, and maybe some others:
2004 2004/10 2004/10/1 10/1 21 october, oct yesterday, today, tomorrow this/next/last week/day/month/quarter/year
Returns a SmartDate, to be converted to a full date later (see fixSmartDate). Assumes any text in the parse stream has been lowercased.
splitSpan :: Interval -> DateSpan -> [DateSpan] Source #
Split a DateSpan into one or more consecutive whole spans of the specified length which enclose it. If no interval is specified, the original span is returned.
Examples:
>>>
let t i d1 d2 = splitSpan i $ mkdatespan d1 d2
>>>
t NoInterval "2008/01/01" "2009/01/01"
[DateSpan 2008]>>>
t (Quarters 1) "2008/01/01" "2009/01/01"
[DateSpan 2008q1,DateSpan 2008q2,DateSpan 2008q3,DateSpan 2008q4]>>>
splitSpan (Quarters 1) nulldatespan
[DateSpan -]>>>
t (Days 1) "2008/01/01" "2008/01/01" -- an empty datespan
[DateSpan 2008/01/01-2007/12/31]>>>
t (Quarters 1) "2008/01/01" "2008/01/01"
[DateSpan 2008/01/01-2007/12/31]>>>
t (Months 1) "2008/01/01" "2008/04/01"
[DateSpan 2008/01,DateSpan 2008/02,DateSpan 2008/03]>>>
t (Months 2) "2008/01/01" "2008/04/01"
[DateSpan 2008/01/01-2008/02/29,DateSpan 2008/03/01-2008/04/30]>>>
t (Weeks 1) "2008/01/01" "2008/01/15"
[DateSpan 2007/12/31w01,DateSpan 2008/01/07w02,DateSpan 2008/01/14w03]>>>
t (Weeks 2) "2008/01/01" "2008/01/15"
[DateSpan 2007/12/31-2008/01/13,DateSpan 2008/01/14-2008/01/27]>>>
t (DayOfMonth 2) "2008/01/01" "2008/04/01"
[DateSpan 2008/01/02-2008/02/01,DateSpan 2008/02/02-2008/03/01,DateSpan 2008/03/02-2008/04/01]>>>
t (DayOfWeek 2) "2011/01/01" "2011/01/15"
[DateSpan 2011/01/04-2011/01/10,DateSpan 2011/01/11-2011/01/17]
fixSmartDate :: Day -> SmartDate -> Day Source #
Convert a SmartDate to an absolute date using the provided reference date.
Examples:
>>>
:set -XOverloadedStrings
>>>
let t = fixSmartDateStr (parsedate "2008/11/26")
>>>
t "0000-01-01"
"0000/01/01">>>
t "1999-12-02"
"1999/12/02">>>
t "1999.12.02"
"1999/12/02">>>
t "1999/3/2"
"1999/03/02">>>
t "19990302"
"1999/03/02">>>
t "2008/2"
"2008/02/01">>>
t "0020/2"
"0020/02/01">>>
t "1000"
"1000/01/01">>>
t "4/2"
"2008/04/02">>>
t "2"
"2008/11/02">>>
t "January"
"2008/01/01">>>
t "feb"
"2008/02/01">>>
t "today"
"2008/11/26">>>
t "yesterday"
"2008/11/25">>>
t "tomorrow"
"2008/11/27">>>
t "this day"
"2008/11/26">>>
t "last day"
"2008/11/25">>>
t "next day"
"2008/11/27">>>
t "this week" -- last monday
"2008/11/24">>>
t "last week" -- previous monday
"2008/11/17">>>
t "next week" -- next monday
"2008/12/01">>>
t "this month"
"2008/11/01">>>
t "last month"
"2008/10/01">>>
t "next month"
"2008/12/01">>>
t "this quarter"
"2008/10/01">>>
t "last quarter"
"2008/07/01">>>
t "next quarter"
"2009/01/01">>>
t "this year"
"2008/01/01">>>
t "last year"
"2007/01/01">>>
t "next year"
"2009/01/01"
t "last wed" "20081119" t "next friday" "20081128" t "next january" "20090101"
fixSmartDateStr :: Day -> Text -> String Source #
Convert a smart date string to an explicit yyyy/mm/dd string using the provided reference date, or raise an error.
fixSmartDateStrEither :: Day -> Text -> Either (ParseError Char MPErr) String Source #
A safe version of fixSmartDateStr.
fixSmartDateStrEither' :: Day -> Text -> Either (ParseError Char MPErr) Day Source #
daysInSpan :: DateSpan -> Maybe Integer Source #
Count the days in a DateSpan, or if it is open-ended return Nothing.
mkdatespan :: String -> String -> DateSpan Source #
Make a datespan from two valid date strings parseable by parsedate (or raise an error). Eg: mkdatespan "201111" "20111231".