Introduce --infer-equity option which will generate conversion postings. --cost will override --infer-equity. This means there will no longer be unbalanced transactions, but will be offsetting conversion postings to balance things out. For example. 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB When converting to cost, this is treated the same as before. When used with --infer-equity, this is now treated as: 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB There is a new account type, Conversion/V, which is a subtype of Equity/E. The first account declared with this type, if any, is used as the base account for inferred equity postings in conversion transactions, overriding the default "equity:conversion". API changes: Costing has been changed to ConversionOp with three options: NoConversionOp, ToCost, and InferEquity. The first correspond to the previous NoCost and Cost options, while the third corresponds to the --infer-equity flag. This converts transactions with costs (one or more transaction prices) to transactions with equity:conversion postings. It is in ConversionOp because converting to cost with -B/--cost and inferring conversion equity postings with --infer-equity are mutually exclusive. Correspondingly, the cost_ record of ReportOpts has been changed to conversionop_. This also removes show_costs_ option in ReportOpts, as its functionality has been replaced by the richer cost_ option.
		
			
				
	
	
		
			49 lines
		
	
	
		
			1.5 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			49 lines
		
	
	
		
			1.5 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| {-# LANGUAGE FlexibleInstances   #-}
 | |
| {-# LANGUAGE OverloadedStrings   #-}
 | |
| {-# LANGUAGE ScopedTypeVariables #-}
 | |
| {-|
 | |
| 
 | |
| Journal entries report, used by the print command.
 | |
| 
 | |
| -}
 | |
| 
 | |
| module Hledger.Reports.EntriesReport (
 | |
|   EntriesReport,
 | |
|   EntriesReportItem,
 | |
|   entriesReport,
 | |
|   -- * Tests
 | |
|   tests_EntriesReport
 | |
| )
 | |
| where
 | |
| 
 | |
| import Data.List (sortBy)
 | |
| import Data.Ord (comparing)
 | |
| import Data.Time (fromGregorian)
 | |
| 
 | |
| import Hledger.Data
 | |
| import Hledger.Query (Query(..))
 | |
| import Hledger.Reports.ReportOptions
 | |
| import Hledger.Utils
 | |
| 
 | |
| 
 | |
| -- | A journal entries report is a list of whole transactions as
 | |
| -- originally entered in the journal (mostly). This is used by eg
 | |
| -- hledger's print command and hledger-web's journal entries view.
 | |
| type EntriesReport = [EntriesReportItem]
 | |
| type EntriesReportItem = Transaction
 | |
| 
 | |
| -- | Select transactions for an entries report.
 | |
| entriesReport :: ReportSpec -> Journal -> EntriesReport
 | |
| entriesReport rspec@ReportSpec{_rsReportOpts=ropts} =
 | |
|     sortBy (comparing $ transactionDateFn ropts) . jtxns
 | |
|     . journalApplyValuationFromOpts (setDefaultConversionOp NoConversionOp rspec)
 | |
|     . filterJournalTransactions (_rsQuery rspec)
 | |
| 
 | |
| tests_EntriesReport = testGroup "EntriesReport" [
 | |
|   testGroup "entriesReport" [
 | |
|      testCase "not acct" $ (length $ entriesReport defreportspec{_rsQuery=Not . Acct $ toRegex' "bank"} samplejournal) @?= 1
 | |
|     ,testCase "date" $ (length $ entriesReport defreportspec{_rsQuery=Date $ DateSpan (Just $ fromGregorian 2008 06 01) (Just $ fromGregorian 2008 07 01)} samplejournal) @?= 3
 | |
|   ]
 | |
|  ]
 | |
| 
 |