rename actual/effective dates to primary/secondary
The command-line flag is now --date2. Alternate spellings --effective and --aux-date are accepted for compatibility.
This commit is contained in:
parent
7d1fce42fe
commit
621a91807e
@ -510,7 +510,7 @@ Right samplejournal = journalBalanceTransactions $
|
||||
{jtxns = [
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2008/01/01",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="",
|
||||
tdescription="income",
|
||||
@ -525,7 +525,7 @@ Right samplejournal = journalBalanceTransactions $
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2008/06/01",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="",
|
||||
tdescription="gift",
|
||||
@ -540,7 +540,7 @@ Right samplejournal = journalBalanceTransactions $
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2008/06/02",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="",
|
||||
tdescription="save",
|
||||
@ -555,7 +555,7 @@ Right samplejournal = journalBalanceTransactions $
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2008/06/03",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=True,
|
||||
tcode="",
|
||||
tdescription="eat & shop",
|
||||
@ -570,7 +570,7 @@ Right samplejournal = journalBalanceTransactions $
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2008/12/31",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="",
|
||||
tdescription="pay off",
|
||||
|
||||
@ -23,7 +23,7 @@ module Hledger.Data.Posting (
|
||||
transactionAllTags,
|
||||
-- * date operations
|
||||
postingDate,
|
||||
postingEffectiveDate,
|
||||
postingDate2,
|
||||
isPostingInDateSpan,
|
||||
postingsDateSpan,
|
||||
-- * account name operations
|
||||
@ -135,14 +135,14 @@ postingDate p = fromMaybe txndate $ pdate p
|
||||
where
|
||||
txndate = maybe nulldate tdate $ ptransaction p
|
||||
|
||||
-- | Get a posting's secondary (effective) date, which is the first of:
|
||||
-- | Get a posting's secondary (secondary) date, which is the first of:
|
||||
-- posting's secondary date, transaction's secondary date, posting's
|
||||
-- primary date, transaction's primary date, or the null date if there is
|
||||
-- no parent transaction.
|
||||
postingEffectiveDate :: Posting -> Day
|
||||
postingEffectiveDate p = headDef nulldate $ catMaybes dates
|
||||
postingDate2 :: Posting -> Day
|
||||
postingDate2 p = headDef nulldate $ catMaybes dates
|
||||
where dates = [pdate2 p
|
||||
,maybe Nothing teffectivedate $ ptransaction p
|
||||
,maybe Nothing tdate2 $ ptransaction p
|
||||
,pdate p
|
||||
,maybe Nothing (Just . tdate) $ ptransaction p
|
||||
]
|
||||
|
||||
@ -77,7 +77,7 @@ entryFromTimeLogInOut i o
|
||||
where
|
||||
t = Transaction {
|
||||
tdate = idate,
|
||||
teffectivedate = Nothing,
|
||||
tdate2 = Nothing,
|
||||
tstatus = True,
|
||||
tcode = "",
|
||||
tdescription = showtime itod ++ "-" ++ showtime otod,
|
||||
|
||||
@ -22,8 +22,7 @@ module Hledger.Data.Transaction (
|
||||
isTransactionBalanced,
|
||||
-- nonzerobalanceerror,
|
||||
-- * date operations
|
||||
transactionActualDate,
|
||||
transactionEffectiveDate,
|
||||
transactionDate2,
|
||||
-- * arithmetic
|
||||
transactionPostingBalances,
|
||||
balanceTransaction,
|
||||
@ -58,7 +57,7 @@ instance Show PeriodicTransaction where
|
||||
nulltransaction :: Transaction
|
||||
nulltransaction = Transaction {
|
||||
tdate=nulldate,
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="",
|
||||
tdescription="",
|
||||
@ -96,7 +95,7 @@ tests_showTransactionUnelided = [
|
||||
nulltransaction `gives` "0000/01/01\n\n"
|
||||
nulltransaction{
|
||||
tdate=parsedate "2012/05/14",
|
||||
teffectivedate=Just $ parsedate "2012/05/15",
|
||||
tdate2=Just $ parsedate "2012/05/15",
|
||||
tstatus=False,
|
||||
tcode="code",
|
||||
tdescription="desc",
|
||||
@ -134,7 +133,7 @@ showTransaction' elide t =
|
||||
++ [""]
|
||||
where
|
||||
descriptionline = rstrip $ concat [date, status, code, desc, inlinecomment]
|
||||
date = showdate (tdate t) ++ maybe "" showedate (teffectivedate t)
|
||||
date = showdate (tdate t) ++ maybe "" showedate (tdate2 t)
|
||||
showdate = printf "%-10s" . showDate
|
||||
showedate = printf "=%s" . showdate
|
||||
status = if tstatus t then " *" else ""
|
||||
@ -342,12 +341,9 @@ nonzerobalanceerror t = printf "could not balance this transaction (%s%s%s)" rms
|
||||
| otherwise = "balanced virtual postings are off by " ++ showMixedAmount (costOfMixedAmount bvsum)
|
||||
sep = if not (null rmsg) && not (null bvmsg) then "; " else "" :: String
|
||||
|
||||
transactionActualDate :: Transaction -> Day
|
||||
transactionActualDate = tdate
|
||||
|
||||
-- Get a transaction's effective date, defaulting to the actual date.
|
||||
transactionEffectiveDate :: Transaction -> Day
|
||||
transactionEffectiveDate t = fromMaybe (tdate t) $ teffectivedate t
|
||||
-- Get a transaction's secondary date, defaulting to the primary date.
|
||||
transactionDate2 :: Transaction -> Day
|
||||
transactionDate2 t = fromMaybe (tdate t) $ tdate2 t
|
||||
|
||||
-- | Ensure a transaction's postings refer back to it.
|
||||
txnTieKnot :: Transaction -> Transaction
|
||||
|
||||
@ -29,7 +29,7 @@ import System.Time (ClockTime)
|
||||
|
||||
type SmartDate = (String,String,String)
|
||||
|
||||
data WhichDate = ActualDate | EffectiveDate deriving (Eq,Show)
|
||||
data WhichDate = PrimaryDate | SecondaryDate deriving (Eq,Show)
|
||||
|
||||
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Show,Ord)
|
||||
|
||||
@ -77,7 +77,7 @@ type Tag = (String, String)
|
||||
|
||||
data Posting = Posting {
|
||||
pdate :: Maybe Day, -- ^ this posting's date, if different from the transaction's
|
||||
pdate2 :: Maybe Day, -- ^ this posting's secondary (effective) date, if different from the transaction's
|
||||
pdate2 :: Maybe Day, -- ^ this posting's secondary date, if different from the transaction's
|
||||
pstatus :: Bool,
|
||||
paccount :: AccountName,
|
||||
pamount :: MixedAmount,
|
||||
@ -95,7 +95,7 @@ instance Eq Posting where
|
||||
|
||||
data Transaction = Transaction {
|
||||
tdate :: Day,
|
||||
teffectivedate :: Maybe Day,
|
||||
tdate2 :: Maybe Day,
|
||||
tstatus :: Bool, -- XXX tcleared ?
|
||||
tcode :: String,
|
||||
tdescription :: String,
|
||||
@ -203,7 +203,7 @@ data CsvRules = CsvRules {
|
||||
baseCurrency :: Maybe String,
|
||||
accountField :: Maybe FieldPosition,
|
||||
account2Field :: Maybe FieldPosition,
|
||||
effectiveDateField :: Maybe FieldPosition,
|
||||
date2Field :: Maybe FieldPosition,
|
||||
baseAccount :: AccountName,
|
||||
accountRules :: [AccountRule],
|
||||
skipLines :: Int
|
||||
|
||||
@ -57,8 +57,8 @@ data Query = Any -- ^ always match
|
||||
| And [Query] -- ^ match if all of these match
|
||||
| Desc String -- ^ match if description matches this regexp
|
||||
| Acct String -- ^ match postings whose account matches this regexp
|
||||
| Date DateSpan -- ^ match if actual date in this date span
|
||||
| EDate DateSpan -- ^ match if effective date in this date span
|
||||
| Date DateSpan -- ^ match if primary date in this date span
|
||||
| Date2 DateSpan -- ^ match if secondary date in this date span
|
||||
| Status Bool -- ^ match if cleared status has this value
|
||||
| Real Bool -- ^ match if "realness" (involves a real non-virtual account ?) has this value
|
||||
| Empty Bool -- ^ if true, show zero-amount postings/accounts which are usually not shown
|
||||
@ -72,7 +72,7 @@ data Query = Any -- ^ always match
|
||||
data QueryOpt = QueryOptInAcctOnly AccountName -- ^ show an account register focussed on this account
|
||||
| QueryOptInAcct AccountName -- ^ as above but include sub-accounts in the account register
|
||||
-- | QueryOptCostBasis -- ^ show amounts converted to cost where possible
|
||||
-- | QueryOptEffectiveDate -- ^ show effective dates instead of actual dates
|
||||
-- | QueryOptDate2 -- ^ show secondary dates instead of primary dates
|
||||
deriving (Show, Eq)
|
||||
|
||||
-- parsing
|
||||
@ -208,7 +208,7 @@ parseQueryTerm d ('d':'a':'t':'e':':':s) =
|
||||
Right (_,span) -> Left $ Date span
|
||||
parseQueryTerm d ('e':'d':'a':'t':'e':':':s) =
|
||||
case parsePeriodExpr d s of Left _ -> Left None -- XXX should warn
|
||||
Right (_,span) -> Left $ EDate span
|
||||
Right (_,span) -> Left $ Date2 span
|
||||
parseQueryTerm _ ('s':'t':'a':'t':'u':'s':':':s) = Left $ Status $ parseStatus s
|
||||
parseQueryTerm _ ('r':'e':'a':'l':':':s) = Left $ Real $ parseBool s
|
||||
parseQueryTerm _ ('e':'m':'p':'t':'y':':':s) = Left $ Empty $ parseBool s
|
||||
@ -337,40 +337,40 @@ queryIsAcct _ = False
|
||||
|
||||
-- | Does this query specify a start date and nothing else (that would
|
||||
-- filter postings prior to the date) ?
|
||||
-- When the flag is true, look for a starting effective date instead.
|
||||
-- When the flag is true, look for a starting secondary date instead.
|
||||
queryIsStartDateOnly :: Bool -> Query -> Bool
|
||||
queryIsStartDateOnly _ Any = False
|
||||
queryIsStartDateOnly _ None = False
|
||||
queryIsStartDateOnly effective (Or ms) = and $ map (queryIsStartDateOnly effective) ms
|
||||
queryIsStartDateOnly effective (And ms) = and $ map (queryIsStartDateOnly effective) ms
|
||||
queryIsStartDateOnly secondary (Or ms) = and $ map (queryIsStartDateOnly secondary) ms
|
||||
queryIsStartDateOnly secondary (And ms) = and $ map (queryIsStartDateOnly secondary) ms
|
||||
queryIsStartDateOnly False (Date (DateSpan (Just _) _)) = True
|
||||
queryIsStartDateOnly True (EDate (DateSpan (Just _) _)) = True
|
||||
queryIsStartDateOnly True (Date2 (DateSpan (Just _) _)) = True
|
||||
queryIsStartDateOnly _ _ = False
|
||||
|
||||
-- | What start date (or effective date) does this query specify, if any ?
|
||||
-- | What start date (or secondary date) does this query specify, if any ?
|
||||
-- For OR expressions, use the earliest of the dates. NOT is ignored.
|
||||
queryStartDate :: Bool -> Query -> Maybe Day
|
||||
queryStartDate effective (Or ms) = earliestMaybeDate $ map (queryStartDate effective) ms
|
||||
queryStartDate effective (And ms) = latestMaybeDate $ map (queryStartDate effective) ms
|
||||
queryStartDate secondary (Or ms) = earliestMaybeDate $ map (queryStartDate secondary) ms
|
||||
queryStartDate secondary (And ms) = latestMaybeDate $ map (queryStartDate secondary) ms
|
||||
queryStartDate False (Date (DateSpan (Just d) _)) = Just d
|
||||
queryStartDate True (EDate (DateSpan (Just d) _)) = Just d
|
||||
queryStartDate True (Date2 (DateSpan (Just d) _)) = Just d
|
||||
queryStartDate _ _ = Nothing
|
||||
|
||||
queryTermDateSpan (Date span) = Just span
|
||||
queryTermDateSpan _ = Nothing
|
||||
|
||||
-- | What date span (or effective date span) does this query specify ?
|
||||
-- | What date span (or secondary date span) does this query specify ?
|
||||
-- For OR expressions, use the widest possible span. NOT is ignored.
|
||||
queryDateSpan :: Bool -> Query -> DateSpan
|
||||
queryDateSpan effective q = spansUnion $ queryDateSpans effective q
|
||||
queryDateSpan secondary q = spansUnion $ queryDateSpans secondary q
|
||||
|
||||
-- | Extract all date (or effective date) spans specified in this query.
|
||||
-- | Extract all date (or secondary date) spans specified in this query.
|
||||
-- NOT is ignored.
|
||||
queryDateSpans :: Bool -> Query -> [DateSpan]
|
||||
queryDateSpans effective (Or qs) = concatMap (queryDateSpans effective) qs
|
||||
queryDateSpans effective (And qs) = concatMap (queryDateSpans effective) qs
|
||||
queryDateSpans secondary (Or qs) = concatMap (queryDateSpans secondary) qs
|
||||
queryDateSpans secondary (And qs) = concatMap (queryDateSpans secondary) qs
|
||||
queryDateSpans False (Date span) = [span]
|
||||
queryDateSpans True (EDate span) = [span]
|
||||
queryDateSpans True (Date2 span) = [span]
|
||||
queryDateSpans _ _ = []
|
||||
|
||||
-- | What is the earliest of these dates, where Nothing is earliest ?
|
||||
@ -457,7 +457,7 @@ tests_matchesAccount = [
|
||||
assertBool "" $ Depth 2 `matchesAccount` "a:b"
|
||||
assertBool "" $ not $ Depth 2 `matchesAccount` "a:b:c"
|
||||
assertBool "" $ Date nulldatespan `matchesAccount` "a"
|
||||
assertBool "" $ EDate nulldatespan `matchesAccount` "a"
|
||||
assertBool "" $ Date2 nulldatespan `matchesAccount` "a"
|
||||
assertBool "" $ not $ (Tag "a" Nothing) `matchesAccount` "a"
|
||||
]
|
||||
|
||||
@ -471,7 +471,7 @@ matchesPosting (And qs) p = all (`matchesPosting` p) qs
|
||||
matchesPosting (Desc r) p = regexMatchesCI r $ maybe "" tdescription $ ptransaction p
|
||||
matchesPosting (Acct r) p = regexMatchesCI r $ paccount p
|
||||
matchesPosting (Date span) p = span `spanContainsDate` postingDate p
|
||||
matchesPosting (EDate span) p = span `spanContainsDate` postingEffectiveDate p
|
||||
matchesPosting (Date2 span) p = span `spanContainsDate` postingDate2 p
|
||||
matchesPosting (Status v) p = v == postingCleared p
|
||||
matchesPosting (Real v) p = v == isReal p
|
||||
matchesPosting (Depth d) Posting{paccount=a} = Depth d `matchesAccount` a
|
||||
@ -521,7 +521,7 @@ matchesTransaction (And qs) t = all (`matchesTransaction` t) qs
|
||||
matchesTransaction (Desc r) t = regexMatchesCI r $ tdescription t
|
||||
matchesTransaction q@(Acct _) t = any (q `matchesPosting`) $ tpostings t
|
||||
matchesTransaction (Date span) t = spanContainsDate span $ tdate t
|
||||
matchesTransaction (EDate span) t = spanContainsDate span $ transactionEffectiveDate t
|
||||
matchesTransaction (Date2 span) t = spanContainsDate span $ transactionDate2 t
|
||||
matchesTransaction (Status v) t = v == tstatus t
|
||||
matchesTransaction (Real v) t = v == hasRealPostings t
|
||||
matchesTransaction (Empty _) _ = True
|
||||
|
||||
@ -96,7 +96,7 @@ nullrules = CsvRules {
|
||||
baseCurrency=Nothing,
|
||||
accountField=Nothing,
|
||||
account2Field=Nothing,
|
||||
effectiveDateField=Nothing,
|
||||
date2Field=Nothing,
|
||||
baseAccount="unknown",
|
||||
accountRules=[],
|
||||
skipLines=0
|
||||
@ -176,7 +176,7 @@ maxFieldIndex r = maximumDef (-1) $ catMaybes [
|
||||
,currencyField r
|
||||
,accountField r
|
||||
,account2Field r
|
||||
,effectiveDateField r
|
||||
,date2Field r
|
||||
]
|
||||
|
||||
-- rulesFileFor :: CliOpts -> FilePath -> FilePath
|
||||
@ -251,7 +251,7 @@ definitions = do
|
||||
,currencyfield
|
||||
,accountfield
|
||||
,account2field
|
||||
,effectivedatefield
|
||||
,date2field
|
||||
,basecurrency
|
||||
,baseaccount
|
||||
,skiplines
|
||||
@ -265,11 +265,11 @@ datefield = do
|
||||
v <- restofline
|
||||
updateState (\r -> r{dateField=readMay v})
|
||||
|
||||
effectivedatefield = do
|
||||
string "effective-date-field"
|
||||
date2field = do
|
||||
string "date2-field"
|
||||
many1 spacenonewline
|
||||
v <- restofline
|
||||
updateState (\r -> r{effectiveDateField=readMay v})
|
||||
updateState (\r -> r{date2Field=readMay v})
|
||||
|
||||
dateformat = do
|
||||
string "date-format"
|
||||
@ -423,7 +423,7 @@ transactionFromCsvRecord :: CsvRules -> CsvRecord -> Transaction
|
||||
transactionFromCsvRecord rules fields =
|
||||
let
|
||||
date = parsedate $ normaliseDate (dateFormat rules) $ maybe "1900/1/1" (atDef "" fields) (dateField rules)
|
||||
effectivedate = do idx <- effectiveDateField rules
|
||||
secondarydate = do idx <- date2Field rules
|
||||
return $ parsedate $ normaliseDate (dateFormat rules) $ (atDef "" fields) idx
|
||||
status = maybe False (null . strip . (atDef "" fields)) (statusField rules)
|
||||
code = maybe "" (atDef "" fields) (codeField rules)
|
||||
@ -449,7 +449,7 @@ transactionFromCsvRecord rules fields =
|
||||
acct = maybe acct' (atDef "" fields) (account2Field rules)
|
||||
t = Transaction {
|
||||
tdate=date,
|
||||
teffectivedate=effectivedate,
|
||||
tdate2=secondarydate,
|
||||
tstatus=status,
|
||||
tcode=code,
|
||||
tdescription=newdesc,
|
||||
|
||||
@ -320,7 +320,7 @@ transaction :: GenParser Char JournalContext Transaction
|
||||
transaction = do
|
||||
-- ptrace "transaction"
|
||||
date <- date <?> "transaction"
|
||||
edate <- optionMaybe (effectivedate date) <?> "effective date"
|
||||
edate <- optionMaybe (secondarydate date) <?> "secondary date"
|
||||
status <- status <?> "cleared flag"
|
||||
code <- code <?> "transaction code"
|
||||
description <- descriptionp >>= return . strip
|
||||
@ -339,7 +339,7 @@ test_transaction = do
|
||||
let Right t2 = p
|
||||
-- same f = assertEqual (f t) (f t2)
|
||||
assertEqual (tdate t) (tdate t2)
|
||||
assertEqual (teffectivedate t) (teffectivedate t2)
|
||||
assertEqual (tdate2 t) (tdate2 t2)
|
||||
assertEqual (tstatus t) (tstatus t2)
|
||||
assertEqual (tcode t) (tcode t2)
|
||||
assertEqual (tdescription t) (tdescription t2)
|
||||
@ -360,7 +360,7 @@ test_transaction = do
|
||||
`gives`
|
||||
nulltransaction{
|
||||
tdate=parsedate "2012/05/14",
|
||||
teffectivedate=Just $ parsedate "2012/05/15",
|
||||
tdate2=Just $ parsedate "2012/05/15",
|
||||
tstatus=False,
|
||||
tcode="code",
|
||||
tdescription="desc",
|
||||
@ -470,17 +470,17 @@ datetime = do
|
||||
-- return $ localTimeToUTC tz' $ LocalTime day $ TimeOfDay h' m' (fromIntegral s')
|
||||
return $ LocalTime day $ TimeOfDay h' m' (fromIntegral s')
|
||||
|
||||
effectivedate :: Day -> GenParser Char JournalContext Day
|
||||
effectivedate actualdate = do
|
||||
secondarydate :: Day -> GenParser Char JournalContext Day
|
||||
secondarydate primarydate = do
|
||||
char '='
|
||||
-- kludgy way to use actual date for default year
|
||||
-- kludgy way to use primary date for default year
|
||||
let withDefaultYear d p = do
|
||||
y <- getYear
|
||||
let (y',_,_) = toGregorian d in setYear y'
|
||||
r <- p
|
||||
when (isJust y) $ setYear $ fromJust y
|
||||
return r
|
||||
edate <- withDefaultYear actualdate date
|
||||
edate <- withDefaultYear primarydate date
|
||||
return edate
|
||||
|
||||
status :: GenParser Char JournalContext Bool
|
||||
|
||||
@ -78,7 +78,7 @@ data ReportOpts = ReportOpts {
|
||||
,cost_ :: Bool
|
||||
,depth_ :: Maybe Int
|
||||
,display_ :: Maybe DisplayExp
|
||||
,effective_ :: Bool
|
||||
,date2_ :: Bool
|
||||
,empty_ :: Bool
|
||||
,no_elide_ :: Bool
|
||||
,real_ :: Bool
|
||||
@ -154,13 +154,13 @@ clearedValueFromOpts ReportOpts{..} | cleared_ = Just True
|
||||
-- depthFromOpts :: ReportOpts -> Int
|
||||
-- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts)
|
||||
|
||||
-- | Report which date we will report on based on --effective.
|
||||
-- | Report which date we will report on based on --date2.
|
||||
whichDateFromOpts :: ReportOpts -> WhichDate
|
||||
whichDateFromOpts ReportOpts{..} = if effective_ then EffectiveDate else ActualDate
|
||||
whichDateFromOpts ReportOpts{..} = if date2_ then SecondaryDate else PrimaryDate
|
||||
|
||||
-- | Select a Transaction date accessor based on --effective.
|
||||
-- | Select a Transaction date accessor based on --date2.
|
||||
transactionDateFn :: ReportOpts -> (Transaction -> Day)
|
||||
transactionDateFn ReportOpts{..} = if effective_ then transactionEffectiveDate else transactionActualDate
|
||||
transactionDateFn ReportOpts{..} = if date2_ then transactionDate2 else tdate
|
||||
|
||||
-- | Convert this journal's postings' amounts to the cost basis amounts if
|
||||
-- specified by options.
|
||||
@ -174,7 +174,7 @@ queryFromOpts :: Day -> ReportOpts -> Query
|
||||
queryFromOpts d opts@ReportOpts{..} = simplifyQuery $ And $ [flagsq, argsq]
|
||||
where
|
||||
flagsq = And $
|
||||
[(if effective_ then EDate else Date) $ dateSpanFromOpts d opts]
|
||||
[(if date2_ then Date2 else Date) $ dateSpanFromOpts d opts]
|
||||
++ (if real_ then [Real True] else [])
|
||||
++ (if empty_ then [Empty True] else []) -- ?
|
||||
++ (maybe [] ((:[]) . Status) (clearedValueFromOpts opts))
|
||||
@ -190,7 +190,7 @@ tests_queryFromOpts = [
|
||||
(queryFromOpts nulldate defreportopts{begin_=Just (parsedate "2012/01/01")
|
||||
,query_="date:'to 2013'"
|
||||
})
|
||||
assertEqual "" (EDate $ mkdatespan "2012/01/01" "2013/01/01")
|
||||
assertEqual "" (Date2 $ mkdatespan "2012/01/01" "2013/01/01")
|
||||
(queryFromOpts nulldate defreportopts{query_="edate:'in 2012'"})
|
||||
assertEqual "" (Or [Acct "a a", Acct "'b"])
|
||||
(queryFromOpts nulldate defreportopts{query_="'a a' 'b"})
|
||||
@ -274,8 +274,8 @@ postingsReport opts q j = -- trace ("q: "++show q++"\nq': "++show q') $
|
||||
-- with period options and any span specified with display option.
|
||||
-- The latter is not easily available, fake it for now.
|
||||
requestedspan = periodspan `spanIntersect` displayspan
|
||||
periodspan = queryDateSpan effectivedate q
|
||||
effectivedate = whichDateFromOpts opts == EffectiveDate
|
||||
periodspan = queryDateSpan secondarydate q
|
||||
secondarydate = whichDateFromOpts opts == SecondaryDate
|
||||
displayspan = postingsDateSpan ps
|
||||
where (_,ps,_) = postingsMatchingDisplayExpr displayexpr $ journalPostings j'
|
||||
matchedspan = postingsDateSpan displayableps
|
||||
@ -303,13 +303,13 @@ mkpostingsReportItem :: Bool -> WhichDate -> Posting -> MixedAmount -> PostingsR
|
||||
mkpostingsReportItem False _ p b = (Nothing, p, b)
|
||||
mkpostingsReportItem True wd p b = (Just (date,desc), p, b)
|
||||
where
|
||||
date = case wd of ActualDate -> postingDate p
|
||||
EffectiveDate -> postingEffectiveDate p
|
||||
date = case wd of PrimaryDate -> postingDate p
|
||||
SecondaryDate -> postingDate2 p
|
||||
desc = maybe "" tdescription $ ptransaction p
|
||||
|
||||
-- | Date-sort and split a list of postings into three spans - postings matched
|
||||
-- by the given display expression, and the preceding and following postings.
|
||||
-- XXX always sorts by primary date, should sort by effective date if expression is about that
|
||||
-- XXX always sorts by primary date, should sort by secondary date if expression is about that
|
||||
postingsMatchingDisplayExpr :: Maybe String -> [Posting] -> ([Posting],[Posting],[Posting])
|
||||
postingsMatchingDisplayExpr d ps = (before, matched, after)
|
||||
where
|
||||
@ -463,7 +463,7 @@ accountTransactionsReport opts j m thisacctquery = (label, items)
|
||||
-- starting balance: if we are filtering by a start date and nothing else,
|
||||
-- the sum of postings to this account before that date; otherwise zero.
|
||||
(startbal,label) | queryIsNull m = (nullmixedamt, balancelabel)
|
||||
| queryIsStartDateOnly (effective_ opts) m = (sumPostings priorps, balancelabel)
|
||||
| queryIsStartDateOnly (date2_ opts) m = (sumPostings priorps, balancelabel)
|
||||
| otherwise = (nullmixedamt, totallabel)
|
||||
where
|
||||
priorps = -- ltrace "priorps" $
|
||||
@ -472,7 +472,7 @@ accountTransactionsReport opts j m thisacctquery = (label, items)
|
||||
And [thisacctquery, tostartdatequery]))
|
||||
$ transactionsPostings ts
|
||||
tostartdatequery = Date (DateSpan Nothing startdate)
|
||||
startdate = queryStartDate (effective_ opts) m
|
||||
startdate = queryStartDate (date2_ opts) m
|
||||
items = reverse $ accountTransactionsReportItems m (Just thisacctquery) startbal negate ts
|
||||
|
||||
-- | Generate transactions report items from a list of transactions,
|
||||
@ -585,7 +585,7 @@ accountBalanceHistory ropts j a = [(getdate t, bal) | (t,_,_,_,_,bal) <- items]
|
||||
(_,items) = journalTransactionsReport ropts j acctquery
|
||||
inclusivebal = True
|
||||
acctquery = Acct $ (if inclusivebal then accountNameToAccountRegex else accountNameToAccountOnlyRegex) $ aname a
|
||||
getdate = if effective_ ropts then transactionEffectiveDate else transactionActualDate
|
||||
getdate = if date2_ ropts then transactionDate2 else tdate
|
||||
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
@ -806,7 +806,7 @@ tests_accountsReport =
|
||||
],
|
||||
Mixed [nullamt])
|
||||
|
||||
,"accountsReport with a date or effective date span" ~: do
|
||||
,"accountsReport with a date or secondary date span" ~: do
|
||||
(defreportopts{query_="date:'in 2009'"}, samplejournal2) `gives`
|
||||
([],
|
||||
Mixed [nullamt])
|
||||
@ -963,7 +963,7 @@ Right samplejournal2 = journalBalanceTransactions $
|
||||
{jtxns = [
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2008/01/01",
|
||||
teffectivedate=Just $ parsedate "2009/01/01",
|
||||
tdate2=Just $ parsedate "2009/01/01",
|
||||
tstatus=False,
|
||||
tcode="",
|
||||
tdescription="income",
|
||||
|
||||
@ -97,7 +97,7 @@ searchform VD{..} = [hamlet|
|
||||
acct:REGEXP (target account), #
|
||||
desc:REGEXP (description), #
|
||||
date:PERIODEXP (date), #
|
||||
edate:PERIODEXP (effective date), #
|
||||
edate:PERIODEXP (secondary date), #
|
||||
<br>
|
||||
status:BOOL (cleared status), #
|
||||
real:BOOL (real/virtual-ness), #
|
||||
|
||||
@ -336,7 +336,7 @@ journal7 = nulljournal {jtxns =
|
||||
[
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2007/01/01",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="*",
|
||||
tdescription="opening balance",
|
||||
@ -351,7 +351,7 @@ journal7 = nulljournal {jtxns =
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2007/02/01",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="*",
|
||||
tdescription="ayres suites",
|
||||
@ -366,7 +366,7 @@ journal7 = nulljournal {jtxns =
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2007/01/02",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="*",
|
||||
tdescription="auto transfer to savings",
|
||||
@ -381,7 +381,7 @@ journal7 = nulljournal {jtxns =
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2007/01/03",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="*",
|
||||
tdescription="poquito mas",
|
||||
@ -396,7 +396,7 @@ journal7 = nulljournal {jtxns =
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2007/01/03",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="*",
|
||||
tdescription="verizon",
|
||||
@ -411,7 +411,7 @@ journal7 = nulljournal {jtxns =
|
||||
,
|
||||
txnTieKnot $ Transaction {
|
||||
tdate=parsedate "2007/01/03",
|
||||
teffectivedate=Nothing,
|
||||
tdate2=Nothing,
|
||||
tstatus=False,
|
||||
tcode="*",
|
||||
tdescription="discover",
|
||||
|
||||
@ -34,7 +34,7 @@ showHistogram opts q j = concatMap (printDayWith countBar) spanps
|
||||
i = intervalFromOpts opts
|
||||
interval | i == NoInterval = Days 1
|
||||
| otherwise = i
|
||||
span = queryDateSpan (effective_ opts) q `orDatesFrom` journalDateSpan j
|
||||
span = queryDateSpan (date2_ opts) q `orDatesFrom` journalDateSpan j
|
||||
spans = filter (DateSpan Nothing Nothing /=) $ splitSpan interval span
|
||||
spanps = [(s, filter (isPostingInDateSpan s) ps) | s <- spans]
|
||||
-- same as Register
|
||||
|
||||
@ -143,7 +143,7 @@ reportflags = [
|
||||
,flagNone ["cost","B"] (\opts -> setboolopt "cost" opts) "report cost of commodities"
|
||||
,flagReq ["depth"] (\s opts -> Right $ setopt "depth" s opts) "N" "hide accounts/transactions deeper than this"
|
||||
,flagReq ["display","d"] (\s opts -> Right $ setopt "display" s opts) "DISPLAYEXP" "show only transactions matching the expression, which is 'dOP[DATE]' where OP is <, <=, =, >=, >"
|
||||
,flagNone ["effective"] (\opts -> setboolopt "effective" opts) "use transactions' effective dates, if any"
|
||||
,flagNone ["date2","aux-date","effective"] (\opts -> setboolopt "date2" opts) "use transactions' secondary dates, if any"
|
||||
,flagNone ["empty","E"] (\opts -> setboolopt "empty" opts) "show empty/zero things which are normally elided"
|
||||
,flagNone ["real","R"] (\opts -> setboolopt "real" opts) "report only on real (non-virtual) transactions"
|
||||
]
|
||||
@ -331,7 +331,7 @@ toCliOpts rawopts = do
|
||||
,cost_ = boolopt "cost" rawopts
|
||||
,depth_ = maybeintopt "depth" rawopts
|
||||
,display_ = maybedisplayopt d rawopts
|
||||
,effective_ = boolopt "effective" rawopts
|
||||
,date2_ = boolopt "date2" rawopts
|
||||
,empty_ = boolopt "empty" rawopts
|
||||
,no_elide_ = boolopt "no-elide" rawopts
|
||||
,real_ = boolopt "real" rawopts
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
hledgerdev -f - balance -p 'in 2009' --effective
|
||||
hledgerdev -f - balance -p 'in 2009' --date2
|
||||
<<<
|
||||
2009/1/1 x
|
||||
a 1
|
||||
@ -1,11 +0,0 @@
|
||||
hledgerdev -f - print
|
||||
<<<
|
||||
2009/1/1=2010/1/1 x
|
||||
a 1
|
||||
b
|
||||
>>>
|
||||
2009/01/01=2010/01/01 x
|
||||
a 1
|
||||
b -1
|
||||
|
||||
>>>=0
|
||||
@ -1,5 +1,5 @@
|
||||
# print shows both dates. The second's year defaults to the first's.
|
||||
hledgerdev -f - print --effective
|
||||
hledgerdev -f - print --date2
|
||||
<<<
|
||||
2009/1/1=1/2 x
|
||||
a 1
|
||||
@ -12,8 +12,8 @@ hledgerdev -f - print --effective
|
||||
>>>2
|
||||
>>>= 0
|
||||
|
||||
# Effective date of 29 Feb on leap year should be valid
|
||||
hledgerdev -f - print --effective
|
||||
# Secondary date of 29 Feb on leap year should be valid
|
||||
hledgerdev -f - print --date2
|
||||
<<<
|
||||
2001/2/27=2000/2/29 x
|
||||
a 1
|
||||
@ -1,4 +1,4 @@
|
||||
hledgerdev -f - register --effective
|
||||
hledgerdev -f - register --date2
|
||||
<<<
|
||||
2009/1/1=2010/1/1 x
|
||||
a 1
|
||||
Loading…
Reference in New Issue
Block a user