refactor: remove costbasis and whichdate from FilterSpec

This commit is contained in:
Simon Michael 2011-06-03 02:14:36 +00:00
parent e8660d98d8
commit dc7a692a19
7 changed files with 25 additions and 30 deletions

View File

@ -54,10 +54,8 @@ nullfilterspec = FilterSpec {
,cleared=Nothing ,cleared=Nothing
,real=False ,real=False
,empty=False ,empty=False
,costbasis=False
,acctpats=[] ,acctpats=[]
,descpats=[] ,descpats=[]
,whichdate=ActualDate
,depth=Nothing ,depth=Nothing
} }
@ -100,38 +98,32 @@ journalAccountNameTree = accountNameTreeFrom . journalAccountNames
-- Various kinds of filtering on journals. We do it differently depending -- Various kinds of filtering on journals. We do it differently depending
-- on the command. -- on the command.
-- | Keep only transactions we are interested in, as described by -- | Keep only transactions we are interested in, as described by the
-- the filter specification. May also massage the data a little. -- filter specification.
filterJournalTransactions :: FilterSpec -> Journal -> Journal filterJournalTransactions :: FilterSpec -> Journal -> Journal
filterJournalTransactions FilterSpec{datespan=datespan filterJournalTransactions FilterSpec{datespan=datespan
,cleared=cleared ,cleared=cleared
-- ,real=real -- ,real=real
-- ,empty=empty -- ,empty=empty
-- ,costbasis=_
,acctpats=apats ,acctpats=apats
,descpats=dpats ,descpats=dpats
,whichdate=whichdate
,depth=depth ,depth=depth
} = } =
filterJournalTransactionsByClearedStatus cleared . filterJournalTransactionsByClearedStatus cleared .
filterJournalPostingsByDepth depth . filterJournalPostingsByDepth depth .
filterJournalTransactionsByAccount apats . filterJournalTransactionsByAccount apats .
filterJournalTransactionsByDescription dpats . filterJournalTransactionsByDescription dpats .
filterJournalTransactionsByDate datespan . filterJournalTransactionsByDate datespan
journalSelectingDate whichdate
-- | Keep only postings we are interested in, as described by -- | Keep only postings we are interested in, as described by the filter
-- the filter specification. May also massage the data a little. -- specification. This can leave unbalanced transactions.
-- This can leave unbalanced transactions.
filterJournalPostings :: FilterSpec -> Journal -> Journal filterJournalPostings :: FilterSpec -> Journal -> Journal
filterJournalPostings FilterSpec{datespan=datespan filterJournalPostings FilterSpec{datespan=datespan
,cleared=cleared ,cleared=cleared
,real=real ,real=real
,empty=empty ,empty=empty
-- ,costbasis=costbasis
,acctpats=apats ,acctpats=apats
,descpats=dpats ,descpats=dpats
,whichdate=whichdate
,depth=depth ,depth=depth
} = } =
filterJournalPostingsByRealness real . filterJournalPostingsByRealness real .
@ -140,8 +132,7 @@ filterJournalPostings FilterSpec{datespan=datespan
filterJournalPostingsByDepth depth . filterJournalPostingsByDepth depth .
filterJournalPostingsByAccount apats . filterJournalPostingsByAccount apats .
filterJournalTransactionsByDescription dpats . filterJournalTransactionsByDescription dpats .
filterJournalTransactionsByDate datespan . filterJournalTransactionsByDate datespan
journalSelectingDate whichdate
-- | Keep only transactions whose description matches the description patterns. -- | Keep only transactions whose description matches the description patterns.
filterJournalTransactionsByDescription :: [String] -> Journal -> Journal filterJournalTransactionsByDescription :: [String] -> Journal -> Journal

View File

@ -193,10 +193,8 @@ data FilterSpec = FilterSpec {
,cleared :: Maybe Bool -- ^ only include if cleared\/uncleared\/don't care ,cleared :: Maybe Bool -- ^ only include if cleared\/uncleared\/don't care
,real :: Bool -- ^ only include if real\/don't care ,real :: Bool -- ^ only include if real\/don't care
,empty :: Bool -- ^ include if empty (ie amount is zero) ,empty :: Bool -- ^ include if empty (ie amount is zero)
,costbasis :: Bool -- ^ convert all amounts to cost basis
,acctpats :: [String] -- ^ only include if matching these account patterns ,acctpats :: [String] -- ^ only include if matching these account patterns
,descpats :: [String] -- ^ only include if matching these description patterns ,descpats :: [String] -- ^ only include if matching these description patterns
,whichdate :: WhichDate -- ^ which dates to use (actual or effective)
,depth :: Maybe Int ,depth :: Maybe Int
} deriving (Show) } deriving (Show)

View File

@ -281,9 +281,10 @@ tests_Hledger_Cli = TestList
"print expenses" ~: "print expenses" ~:
do do
let args = ["expenses"] let args = ["expenses"]
l <- samplejournalwithopts [] args opts = []
l <- samplejournalwithopts opts args
t <- getCurrentLocalTime t <- getCurrentLocalTime
showTransactions (optsToFilterSpec [] args t) l `is` unlines showTransactions opts (optsToFilterSpec opts args t) l `is` unlines
["2008/06/03 * eat & shop" ["2008/06/03 * eat & shop"
," expenses:food $1" ," expenses:food $1"
," expenses:supplies $1" ," expenses:supplies $1"
@ -295,7 +296,7 @@ tests_Hledger_Cli = TestList
do do
l <- samplejournal l <- samplejournal
t <- getCurrentLocalTime t <- getCurrentLocalTime
showTransactions (optsToFilterSpec [Depth "2"] [] t) l `is` unlines showTransactions [] (optsToFilterSpec [Depth "2"] [] t) l `is` unlines
["2008/01/01 income" ["2008/01/01 income"
," income:salary $-1" ," income:salary $-1"
,"" ,""

View File

@ -131,7 +131,8 @@ type BalanceReportItem = (AccountName -- full account name
balance :: [Opt] -> [String] -> Journal -> IO () balance :: [Opt] -> [String] -> Journal -> IO ()
balance opts args j = do balance opts args j = do
t <- getCurrentLocalTime t <- getCurrentLocalTime
putStr $ balanceReportAsText opts $ balanceReport opts (optsToFilterSpec opts args t) j let j' = journalSelectingDate (whichDateFromOpts opts) j
putStr $ balanceReportAsText opts $ balanceReport opts (optsToFilterSpec opts args t) j'
-- | Render a balance report as plain text suitable for console output. -- | Render a balance report as plain text suitable for console output.
balanceReportAsText :: [Opt] -> BalanceReport -> String balanceReportAsText :: [Opt] -> BalanceReport -> String

View File

@ -249,6 +249,10 @@ clearedValueFromOpts opts | null os = Nothing
| otherwise = Just False | otherwise = Just False
where os = optsWithConstructors [Cleared,UnCleared] opts where os = optsWithConstructors [Cleared,UnCleared] opts
-- | Detect which date we will report on, based on --effective.
whichDateFromOpts :: [Opt] -> WhichDate
whichDateFromOpts opts = if Effective `elem` opts then EffectiveDate else ActualDate
-- | Were we invoked as \"hours\" ? -- | Were we invoked as \"hours\" ?
usingTimeProgramName :: IO Bool usingTimeProgramName :: IO Bool
usingTimeProgramName = do usingTimeProgramName = do
@ -281,10 +285,8 @@ optsToFilterSpec opts args t = FilterSpec {
,cleared=clearedValueFromOpts opts ,cleared=clearedValueFromOpts opts
,real=Real `elem` opts ,real=Real `elem` opts
,empty=Empty `elem` opts ,empty=Empty `elem` opts
,costbasis=CostBasis `elem` opts
,acctpats=apats ,acctpats=apats
,descpats=dpats ,descpats=dpats
,whichdate = if Effective `elem` opts then EffectiveDate else ActualDate
,depth = depthFromOpts opts ,depth = depthFromOpts opts
} }
where (apats,dpats) = parsePatternArgs args where (apats,dpats) = parsePatternArgs args

View File

@ -28,14 +28,15 @@ type JournalReportItem = Transaction
print' :: [Opt] -> [String] -> Journal -> IO () print' :: [Opt] -> [String] -> Journal -> IO ()
print' opts args j = do print' opts args j = do
t <- getCurrentLocalTime t <- getCurrentLocalTime
putStr $ showTransactions (optsToFilterSpec opts args t) j let j' = journalSelectingDate (whichDateFromOpts opts) j
putStr $ showTransactions opts (optsToFilterSpec opts args t) j'
showTransactions :: FilterSpec -> Journal -> String showTransactions :: [Opt] -> FilterSpec -> Journal -> String
showTransactions fspec j = journalReportAsText [] fspec $ journalReport [] fspec j showTransactions opts fspec j = journalReportAsText opts fspec $ journalReport [] fspec j
journalReportAsText :: [Opt] -> FilterSpec -> JournalReport -> String -- XXX unlike the others, this one needs fspec not opts journalReportAsText :: [Opt] -> FilterSpec -> JournalReport -> String
journalReportAsText _ fspec items = concatMap (showTransactionForPrint effective) items journalReportAsText opts _ items = concatMap (showTransactionForPrint effective) items
where effective = EffectiveDate == whichdate fspec where effective = Effective `elem` opts
journalReport :: [Opt] -> FilterSpec -> Journal -> JournalReport journalReport :: [Opt] -> FilterSpec -> Journal -> JournalReport
journalReport _ fspec j = sortBy (comparing tdate) $ jtxns $ filterJournalTransactions fspec j journalReport _ fspec j = sortBy (comparing tdate) $ jtxns $ filterJournalTransactions fspec j

View File

@ -78,7 +78,8 @@ registerReport opts fspec j = getitems ps nullposting startbal
(precedingps, displayableps, _) = postingsMatchingDisplayExpr (displayExprFromOpts opts) (precedingps, displayableps, _) = postingsMatchingDisplayExpr (displayExprFromOpts opts)
$ depthClipPostings depth $ depthClipPostings depth
$ journalPostings $ journalPostings
$ filterJournalPostings fspec{depth=Nothing} j $ filterJournalPostings fspec{depth=Nothing} j'
j' = journalSelectingDate (whichDateFromOpts opts) j
startbal = sumPostings precedingps startbal = sumPostings precedingps
filterspan = datespan fspec filterspan = datespan fspec
(interval, depth, empty) = (intervalFromOpts opts, depthFromOpts opts, Empty `elem` opts) (interval, depth, empty) = (intervalFromOpts opts, depthFromOpts opts, Empty `elem` opts)